{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GdkDmabufTextureBuilder@ is a builder used to construct t'GI.Gdk.Objects.Texture.Texture'
-- objects from DMA buffers.
-- 
-- DMA buffers are commonly called **_dma-bufs_**.
-- 
-- DMA buffers are a feature of the Linux kernel to enable efficient buffer and
-- memory sharing between hardware such as codecs, GPUs, displays, cameras and the
-- kernel drivers controlling them. For example, a decoder may want its output to
-- be directly shared with the display server for rendering without a copy.
-- 
-- Any device driver which participates in DMA buffer sharing, can do so as either
-- the exporter or importer of buffers (or both).
-- 
-- The memory that is shared via DMA buffers is usually stored in non-system memory
-- (maybe in device\'s local memory or something else not directly accessible by the
-- CPU), and accessing this memory from the CPU may have higher-than-usual overhead.
-- 
-- In particular for graphics data, it is not uncommon that data consists of multiple
-- separate blocks of memory, for example one block for each of the red, green and
-- blue channels. These blocks are called **_planes_**. DMA buffers can have up to
-- four planes. Even if the memory is a single block, the data can be organized in
-- multiple planes, by specifying offsets from the beginning of the data.
-- 
-- DMA buffers are exposed to user-space as file descriptors allowing to pass them
-- between processes. If a DMA buffer has multiple planes, there is one file
-- descriptor per plane.
-- 
-- The format of the data (for graphics data, essentially its colorspace) is described
-- by a 32-bit integer. These format identifiers are defined in the header file @drm_fourcc.h@
-- and commonly referred to as **_fourcc_** values, since they are identified by 4 ASCII
-- characters. Additionally, each DMA buffer has a **_modifier_**, which is a 64-bit integer
-- that describes driver-specific details of the memory layout, such as tiling or compression.
-- 
-- For historical reasons, some producers of dma-bufs don\'t provide an explicit modifier, but
-- instead return @DMA_FORMAT_MOD_INVALID@ to indicate that their modifier is **_implicit_**.
-- GTK tries to accommodate this situation by accepting @DMA_FORMAT_MOD_INVALID@ as modifier.
-- 
-- The operation of @GdkDmabufTextureBuilder@ is quite simple: Create a texture builder,
-- set all the necessary properties, and then call 'GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderBuild'
-- to create the new texture.
-- 
-- The required properties for a dma-buf texture are
-- 
--  * The width and height in pixels
-- 
--  * The @fourcc@ code and @modifier@ which identify the format and memory layout of the dma-buf
-- 
--  * The file descriptor, offset and stride for each of the planes
-- 
-- @GdkDmabufTextureBuilder@ can be used for quick one-shot construction of
-- textures as well as kept around and reused to construct multiple textures.
-- 
-- For further information, see
-- 
-- * The Linux kernel <https://docs.kernel.org/driver-api/dma-buf.html documentation>
-- 
-- * The header file <https://gitlab.freedesktop.org/mesa/drm/-/blob/main/include/drm/drm_fourcc.h drm_fourcc.h>
-- 
-- /Since: 4.14/

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

module GI.Gdk.Objects.DmabufTextureBuilder
    ( 

-- * Exported types
    DmabufTextureBuilder(..)                ,
    IsDmabufTextureBuilder                  ,
    toDmabufTextureBuilder                  ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [build]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:build"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDisplay]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getDisplay"), [getFd]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getFd"), [getFourcc]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getFourcc"), [getHeight]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getHeight"), [getModifier]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getModifier"), [getNPlanes]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getNPlanes"), [getOffset]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getOffset"), [getPremultiplied]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getPremultiplied"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStride]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getStride"), [getUpdateRegion]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getUpdateRegion"), [getUpdateTexture]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getUpdateTexture"), [getWidth]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:getWidth").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDisplay]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setDisplay"), [setFd]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setFd"), [setFourcc]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setFourcc"), [setHeight]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setHeight"), [setModifier]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setModifier"), [setNPlanes]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setNPlanes"), [setOffset]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setOffset"), [setPremultiplied]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setPremultiplied"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setStride]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setStride"), [setUpdateRegion]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setUpdateRegion"), [setUpdateTexture]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setUpdateTexture"), [setWidth]("GI.Gdk.Objects.DmabufTextureBuilder#g:method:setWidth").

#if defined(ENABLE_OVERLOADING)
    ResolveDmabufTextureBuilderMethod       ,
#endif

-- ** build #method:build#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderBuildMethodInfo     ,
#endif
    dmabufTextureBuilderBuild               ,


-- ** getDisplay #method:getDisplay#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetDisplayMethodInfo,
#endif
    dmabufTextureBuilderGetDisplay          ,


-- ** getFd #method:getFd#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetFdMethodInfo     ,
#endif
    dmabufTextureBuilderGetFd               ,


-- ** getFourcc #method:getFourcc#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetFourccMethodInfo ,
#endif
    dmabufTextureBuilderGetFourcc           ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetHeightMethodInfo ,
#endif
    dmabufTextureBuilderGetHeight           ,


-- ** getModifier #method:getModifier#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetModifierMethodInfo,
#endif
    dmabufTextureBuilderGetModifier         ,


-- ** getNPlanes #method:getNPlanes#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetNPlanesMethodInfo,
#endif
    dmabufTextureBuilderGetNPlanes          ,


-- ** getOffset #method:getOffset#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetOffsetMethodInfo ,
#endif
    dmabufTextureBuilderGetOffset           ,


-- ** getPremultiplied #method:getPremultiplied#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetPremultipliedMethodInfo,
#endif
    dmabufTextureBuilderGetPremultiplied    ,


-- ** getStride #method:getStride#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetStrideMethodInfo ,
#endif
    dmabufTextureBuilderGetStride           ,


-- ** getUpdateRegion #method:getUpdateRegion#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetUpdateRegionMethodInfo,
#endif
    dmabufTextureBuilderGetUpdateRegion     ,


-- ** getUpdateTexture #method:getUpdateTexture#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetUpdateTextureMethodInfo,
#endif
    dmabufTextureBuilderGetUpdateTexture    ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderGetWidthMethodInfo  ,
#endif
    dmabufTextureBuilderGetWidth            ,


-- ** new #method:new#

    dmabufTextureBuilderNew                 ,


-- ** setDisplay #method:setDisplay#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetDisplayMethodInfo,
#endif
    dmabufTextureBuilderSetDisplay          ,


-- ** setFd #method:setFd#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetFdMethodInfo     ,
#endif
    dmabufTextureBuilderSetFd               ,


-- ** setFourcc #method:setFourcc#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetFourccMethodInfo ,
#endif
    dmabufTextureBuilderSetFourcc           ,


-- ** setHeight #method:setHeight#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetHeightMethodInfo ,
#endif
    dmabufTextureBuilderSetHeight           ,


-- ** setModifier #method:setModifier#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetModifierMethodInfo,
#endif
    dmabufTextureBuilderSetModifier         ,


-- ** setNPlanes #method:setNPlanes#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetNPlanesMethodInfo,
#endif
    dmabufTextureBuilderSetNPlanes          ,


-- ** setOffset #method:setOffset#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetOffsetMethodInfo ,
#endif
    dmabufTextureBuilderSetOffset           ,


-- ** setPremultiplied #method:setPremultiplied#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetPremultipliedMethodInfo,
#endif
    dmabufTextureBuilderSetPremultiplied    ,


-- ** setStride #method:setStride#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetStrideMethodInfo ,
#endif
    dmabufTextureBuilderSetStride           ,


-- ** setUpdateRegion #method:setUpdateRegion#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetUpdateRegionMethodInfo,
#endif
    dmabufTextureBuilderSetUpdateRegion     ,


-- ** setUpdateTexture #method:setUpdateTexture#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetUpdateTextureMethodInfo,
#endif
    dmabufTextureBuilderSetUpdateTexture    ,


-- ** setWidth #method:setWidth#

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderSetWidthMethodInfo  ,
#endif
    dmabufTextureBuilderSetWidth            ,




 -- * Properties


-- ** display #attr:display#
-- | The display that this texture will be used on.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderDisplayPropertyInfo ,
#endif
    constructDmabufTextureBuilderDisplay    ,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderDisplay             ,
#endif
    getDmabufTextureBuilderDisplay          ,
    setDmabufTextureBuilderDisplay          ,


-- ** fourcc #attr:fourcc#
-- | The format of the texture, as a fourcc value.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderFourccPropertyInfo  ,
#endif
    constructDmabufTextureBuilderFourcc     ,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderFourcc              ,
#endif
    getDmabufTextureBuilderFourcc           ,
    setDmabufTextureBuilderFourcc           ,


-- ** height #attr:height#
-- | The height of the texture.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderHeightPropertyInfo  ,
#endif
    constructDmabufTextureBuilderHeight     ,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderHeight              ,
#endif
    getDmabufTextureBuilderHeight           ,
    setDmabufTextureBuilderHeight           ,


-- ** modifier #attr:modifier#
-- | The modifier.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderModifierPropertyInfo,
#endif
    constructDmabufTextureBuilderModifier   ,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderModifier            ,
#endif
    getDmabufTextureBuilderModifier         ,
    setDmabufTextureBuilderModifier         ,


-- ** nPlanes #attr:nPlanes#
-- | The number of planes of the texture.
-- 
-- Note that you can set properties for other planes,
-- but they will be ignored when constructing the texture.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderNPlanesPropertyInfo ,
#endif
    constructDmabufTextureBuilderNPlanes    ,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderNPlanes             ,
#endif
    getDmabufTextureBuilderNPlanes          ,
    setDmabufTextureBuilderNPlanes          ,


-- ** premultiplied #attr:premultiplied#
-- | Whether the alpha channel is premultiplied into the others.
-- 
-- Only relevant if the format has alpha.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderPremultipliedPropertyInfo,
#endif
    constructDmabufTextureBuilderPremultiplied,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderPremultiplied       ,
#endif
    getDmabufTextureBuilderPremultiplied    ,
    setDmabufTextureBuilderPremultiplied    ,


-- ** updateRegion #attr:updateRegion#
-- | The update region for [GLTextureBuilder:updateTexture]("GI.Gdk.Objects.GLTextureBuilder#g:attr:updateTexture").
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderUpdateRegionPropertyInfo,
#endif
    clearDmabufTextureBuilderUpdateRegion   ,
    constructDmabufTextureBuilderUpdateRegion,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderUpdateRegion        ,
#endif
    getDmabufTextureBuilderUpdateRegion     ,
    setDmabufTextureBuilderUpdateRegion     ,


-- ** updateTexture #attr:updateTexture#
-- | The texture [DmabufTextureBuilder:updateRegion]("GI.Gdk.Objects.DmabufTextureBuilder#g:attr:updateRegion") is an update for.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderUpdateTexturePropertyInfo,
#endif
    clearDmabufTextureBuilderUpdateTexture  ,
    constructDmabufTextureBuilderUpdateTexture,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderUpdateTexture       ,
#endif
    getDmabufTextureBuilderUpdateTexture    ,
    setDmabufTextureBuilderUpdateTexture    ,


-- ** width #attr:width#
-- | The width of the texture.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    DmabufTextureBuilderWidthPropertyInfo   ,
#endif
    constructDmabufTextureBuilderWidth      ,
#if defined(ENABLE_OVERLOADING)
    dmabufTextureBuilderWidth               ,
#endif
    getDmabufTextureBuilderWidth            ,
    setDmabufTextureBuilderWidth            ,




    ) 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.CairoContext as Gdk.CairoContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import {-# SOURCE #-} qualified GI.Gdk.Objects.ContentProvider as Gdk.ContentProvider
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawContext as Gdk.DrawContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Event as Gdk.Event
import {-# SOURCE #-} qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import {-# SOURCE #-} qualified GI.Gdk.Objects.GLContext as Gdk.GLContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import {-# SOURCE #-} qualified GI.Gdk.Objects.Surface as Gdk.Surface
import {-# SOURCE #-} qualified GI.Gdk.Objects.Texture as Gdk.Texture
import {-# SOURCE #-} qualified GI.Gdk.Objects.VulkanContext as Gdk.VulkanContext
import {-# SOURCE #-} qualified GI.Gdk.Structs.ContentFormats as Gdk.ContentFormats
import {-# SOURCE #-} qualified GI.Gdk.Structs.DmabufFormats as Gdk.DmabufFormats
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.KeymapKey as Gdk.KeymapKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.TimeCoord as Gdk.TimeCoord
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gio.Interfaces.LoadableIcon as Gio.LoadableIcon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.InputStream as Gio.InputStream
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import qualified GI.Pango.Enums as Pango.Enums

#else
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.Texture as Gdk.Texture

#endif

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

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

foreign import ccall "gdk_dmabuf_texture_builder_get_type"
    c_gdk_dmabuf_texture_builder_get_type :: IO B.Types.GType

instance B.Types.TypedObject DmabufTextureBuilder where
    glibType :: IO GType
glibType = IO GType
c_gdk_dmabuf_texture_builder_get_type

instance B.Types.GObject DmabufTextureBuilder

-- | Type class for types which can be safely cast to `DmabufTextureBuilder`, for instance with `toDmabufTextureBuilder`.
class (SP.GObject o, O.IsDescendantOf DmabufTextureBuilder o) => IsDmabufTextureBuilder o
instance (SP.GObject o, O.IsDescendantOf DmabufTextureBuilder o) => IsDmabufTextureBuilder o

instance O.HasParentTypes DmabufTextureBuilder
type instance O.ParentTypes DmabufTextureBuilder = '[GObject.Object.Object]

-- | Cast to `DmabufTextureBuilder`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDmabufTextureBuilder :: (MIO.MonadIO m, IsDmabufTextureBuilder o) => o -> m DmabufTextureBuilder
toDmabufTextureBuilder :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m DmabufTextureBuilder
toDmabufTextureBuilder = IO DmabufTextureBuilder -> m DmabufTextureBuilder
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DmabufTextureBuilder -> m DmabufTextureBuilder)
-> (o -> IO DmabufTextureBuilder) -> o -> m DmabufTextureBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DmabufTextureBuilder -> DmabufTextureBuilder)
-> o -> IO DmabufTextureBuilder
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DmabufTextureBuilder -> DmabufTextureBuilder
DmabufTextureBuilder

-- | Convert 'DmabufTextureBuilder' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe DmabufTextureBuilder) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_dmabuf_texture_builder_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DmabufTextureBuilder -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DmabufTextureBuilder
P.Nothing = Ptr GValue -> Ptr DmabufTextureBuilder -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DmabufTextureBuilder
forall a. Ptr a
FP.nullPtr :: FP.Ptr DmabufTextureBuilder)
    gvalueSet_ Ptr GValue
gv (P.Just DmabufTextureBuilder
obj) = DmabufTextureBuilder
-> (Ptr DmabufTextureBuilder -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DmabufTextureBuilder
obj (Ptr GValue -> Ptr DmabufTextureBuilder -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DmabufTextureBuilder)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr DmabufTextureBuilder)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DmabufTextureBuilder)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newObject DmabufTextureBuilder ptr
        else return P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDmabufTextureBuilderMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDmabufTextureBuilderMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDmabufTextureBuilderMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDmabufTextureBuilderMethod "build" o = DmabufTextureBuilderBuildMethodInfo
    ResolveDmabufTextureBuilderMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDmabufTextureBuilderMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDmabufTextureBuilderMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDmabufTextureBuilderMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDmabufTextureBuilderMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDmabufTextureBuilderMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDmabufTextureBuilderMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDmabufTextureBuilderMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDmabufTextureBuilderMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDmabufTextureBuilderMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDmabufTextureBuilderMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDmabufTextureBuilderMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDmabufTextureBuilderMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDmabufTextureBuilderMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDmabufTextureBuilderMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDmabufTextureBuilderMethod "getDisplay" o = DmabufTextureBuilderGetDisplayMethodInfo
    ResolveDmabufTextureBuilderMethod "getFd" o = DmabufTextureBuilderGetFdMethodInfo
    ResolveDmabufTextureBuilderMethod "getFourcc" o = DmabufTextureBuilderGetFourccMethodInfo
    ResolveDmabufTextureBuilderMethod "getHeight" o = DmabufTextureBuilderGetHeightMethodInfo
    ResolveDmabufTextureBuilderMethod "getModifier" o = DmabufTextureBuilderGetModifierMethodInfo
    ResolveDmabufTextureBuilderMethod "getNPlanes" o = DmabufTextureBuilderGetNPlanesMethodInfo
    ResolveDmabufTextureBuilderMethod "getOffset" o = DmabufTextureBuilderGetOffsetMethodInfo
    ResolveDmabufTextureBuilderMethod "getPremultiplied" o = DmabufTextureBuilderGetPremultipliedMethodInfo
    ResolveDmabufTextureBuilderMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDmabufTextureBuilderMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDmabufTextureBuilderMethod "getStride" o = DmabufTextureBuilderGetStrideMethodInfo
    ResolveDmabufTextureBuilderMethod "getUpdateRegion" o = DmabufTextureBuilderGetUpdateRegionMethodInfo
    ResolveDmabufTextureBuilderMethod "getUpdateTexture" o = DmabufTextureBuilderGetUpdateTextureMethodInfo
    ResolveDmabufTextureBuilderMethod "getWidth" o = DmabufTextureBuilderGetWidthMethodInfo
    ResolveDmabufTextureBuilderMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDmabufTextureBuilderMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDmabufTextureBuilderMethod "setDisplay" o = DmabufTextureBuilderSetDisplayMethodInfo
    ResolveDmabufTextureBuilderMethod "setFd" o = DmabufTextureBuilderSetFdMethodInfo
    ResolveDmabufTextureBuilderMethod "setFourcc" o = DmabufTextureBuilderSetFourccMethodInfo
    ResolveDmabufTextureBuilderMethod "setHeight" o = DmabufTextureBuilderSetHeightMethodInfo
    ResolveDmabufTextureBuilderMethod "setModifier" o = DmabufTextureBuilderSetModifierMethodInfo
    ResolveDmabufTextureBuilderMethod "setNPlanes" o = DmabufTextureBuilderSetNPlanesMethodInfo
    ResolveDmabufTextureBuilderMethod "setOffset" o = DmabufTextureBuilderSetOffsetMethodInfo
    ResolveDmabufTextureBuilderMethod "setPremultiplied" o = DmabufTextureBuilderSetPremultipliedMethodInfo
    ResolveDmabufTextureBuilderMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDmabufTextureBuilderMethod "setStride" o = DmabufTextureBuilderSetStrideMethodInfo
    ResolveDmabufTextureBuilderMethod "setUpdateRegion" o = DmabufTextureBuilderSetUpdateRegionMethodInfo
    ResolveDmabufTextureBuilderMethod "setUpdateTexture" o = DmabufTextureBuilderSetUpdateTextureMethodInfo
    ResolveDmabufTextureBuilderMethod "setWidth" o = DmabufTextureBuilderSetWidthMethodInfo
    ResolveDmabufTextureBuilderMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDmabufTextureBuilderMethod t DmabufTextureBuilder, O.OverloadedMethod info DmabufTextureBuilder p, R.HasField t DmabufTextureBuilder p) => R.HasField t DmabufTextureBuilder p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveDmabufTextureBuilderMethod t DmabufTextureBuilder, O.OverloadedMethodInfo info DmabufTextureBuilder) => OL.IsLabel t (O.MethodProxy info DmabufTextureBuilder) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "display"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Display"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@display@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #display
-- @
getDmabufTextureBuilderDisplay :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m Gdk.Display.Display
getDmabufTextureBuilderDisplay :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m Display
getDmabufTextureBuilderDisplay o
obj = IO Display -> m Display
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Display -> m Display) -> IO Display -> m Display
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Display) -> IO Display
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDmabufTextureBuilderDisplay" (IO (Maybe Display) -> IO Display)
-> IO (Maybe Display) -> IO Display
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Display -> Display) -> IO (Maybe Display)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"display" ManagedPtr Display -> Display
Gdk.Display.Display

-- | Set the value of the “@display@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #display 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderDisplay :: (MonadIO m, IsDmabufTextureBuilder o, Gdk.Display.IsDisplay a) => o -> a -> m ()
setDmabufTextureBuilderDisplay :: forall (m :: * -> *) o a.
(MonadIO m, IsDmabufTextureBuilder o, IsDisplay a) =>
o -> a -> m ()
setDmabufTextureBuilderDisplay o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"display" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@display@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderDisplay :: (IsDmabufTextureBuilder o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructDmabufTextureBuilderDisplay :: forall o (m :: * -> *) a.
(IsDmabufTextureBuilder o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructDmabufTextureBuilderDisplay a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"display" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderDisplayPropertyInfo
instance AttrInfo DmabufTextureBuilderDisplayPropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderDisplayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DmabufTextureBuilderDisplayPropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint DmabufTextureBuilderDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType DmabufTextureBuilderDisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType DmabufTextureBuilderDisplayPropertyInfo = Gdk.Display.Display
    type AttrLabel DmabufTextureBuilderDisplayPropertyInfo = "display"
    type AttrOrigin DmabufTextureBuilderDisplayPropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderDisplay
    attrSet = setDmabufTextureBuilderDisplay
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructDmabufTextureBuilderDisplay
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.display"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:display"
        })
#endif

-- VVV Prop "fourcc"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@fourcc@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #fourcc
-- @
getDmabufTextureBuilderFourcc :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m Word32
getDmabufTextureBuilderFourcc :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m Word32
getDmabufTextureBuilderFourcc o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"fourcc"

-- | Set the value of the “@fourcc@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #fourcc 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderFourcc :: (MonadIO m, IsDmabufTextureBuilder o) => o -> Word32 -> m ()
setDmabufTextureBuilderFourcc :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> Word32 -> m ()
setDmabufTextureBuilderFourcc o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"fourcc" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@fourcc@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderFourcc :: (IsDmabufTextureBuilder o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDmabufTextureBuilderFourcc :: forall o (m :: * -> *).
(IsDmabufTextureBuilder o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructDmabufTextureBuilderFourcc Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"fourcc" Word32
val

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderFourccPropertyInfo
instance AttrInfo DmabufTextureBuilderFourccPropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderFourccPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DmabufTextureBuilderFourccPropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderFourccPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint DmabufTextureBuilderFourccPropertyInfo = (~) Word32
    type AttrTransferType DmabufTextureBuilderFourccPropertyInfo = Word32
    type AttrGetType DmabufTextureBuilderFourccPropertyInfo = Word32
    type AttrLabel DmabufTextureBuilderFourccPropertyInfo = "fourcc"
    type AttrOrigin DmabufTextureBuilderFourccPropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderFourcc
    attrSet = setDmabufTextureBuilderFourcc
    attrTransfer _ v = do
        return v
    attrConstruct = constructDmabufTextureBuilderFourcc
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.fourcc"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:fourcc"
        })
#endif

-- VVV Prop "height"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #height
-- @
getDmabufTextureBuilderHeight :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m Word32
getDmabufTextureBuilderHeight :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m Word32
getDmabufTextureBuilderHeight o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"height"

-- | Set the value of the “@height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #height 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderHeight :: (MonadIO m, IsDmabufTextureBuilder o) => o -> Word32 -> m ()
setDmabufTextureBuilderHeight :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> Word32 -> m ()
setDmabufTextureBuilderHeight o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"height" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@height@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderHeight :: (IsDmabufTextureBuilder o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDmabufTextureBuilderHeight :: forall o (m :: * -> *).
(IsDmabufTextureBuilder o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructDmabufTextureBuilderHeight Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"height" Word32
val

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderHeightPropertyInfo
instance AttrInfo DmabufTextureBuilderHeightPropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DmabufTextureBuilderHeightPropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderHeightPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint DmabufTextureBuilderHeightPropertyInfo = (~) Word32
    type AttrTransferType DmabufTextureBuilderHeightPropertyInfo = Word32
    type AttrGetType DmabufTextureBuilderHeightPropertyInfo = Word32
    type AttrLabel DmabufTextureBuilderHeightPropertyInfo = "height"
    type AttrOrigin DmabufTextureBuilderHeightPropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderHeight
    attrSet = setDmabufTextureBuilderHeight
    attrTransfer _ v = do
        return v
    attrConstruct = constructDmabufTextureBuilderHeight
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.height"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:height"
        })
#endif

-- VVV Prop "modifier"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@modifier@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #modifier
-- @
getDmabufTextureBuilderModifier :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m Word64
getDmabufTextureBuilderModifier :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m Word64
getDmabufTextureBuilderModifier o
obj = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word64
forall a. GObject a => a -> String -> IO Word64
B.Properties.getObjectPropertyUInt64 o
obj String
"modifier"

-- | Set the value of the “@modifier@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #modifier 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderModifier :: (MonadIO m, IsDmabufTextureBuilder o) => o -> Word64 -> m ()
setDmabufTextureBuilderModifier :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> Word64 -> m ()
setDmabufTextureBuilderModifier o
obj Word64
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word64 -> IO ()
forall a. GObject a => a -> String -> Word64 -> IO ()
B.Properties.setObjectPropertyUInt64 o
obj String
"modifier" Word64
val

-- | Construct a `GValueConstruct` with valid value for the “@modifier@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderModifier :: (IsDmabufTextureBuilder o, MIO.MonadIO m) => Word64 -> m (GValueConstruct o)
constructDmabufTextureBuilderModifier :: forall o (m :: * -> *).
(IsDmabufTextureBuilder o, MonadIO m) =>
Word64 -> m (GValueConstruct o)
constructDmabufTextureBuilderModifier Word64
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word64 -> IO (GValueConstruct o)
forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 String
"modifier" Word64
val

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderModifierPropertyInfo
instance AttrInfo DmabufTextureBuilderModifierPropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderModifierPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DmabufTextureBuilderModifierPropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderModifierPropertyInfo = (~) Word64
    type AttrTransferTypeConstraint DmabufTextureBuilderModifierPropertyInfo = (~) Word64
    type AttrTransferType DmabufTextureBuilderModifierPropertyInfo = Word64
    type AttrGetType DmabufTextureBuilderModifierPropertyInfo = Word64
    type AttrLabel DmabufTextureBuilderModifierPropertyInfo = "modifier"
    type AttrOrigin DmabufTextureBuilderModifierPropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderModifier
    attrSet = setDmabufTextureBuilderModifier
    attrTransfer _ v = do
        return v
    attrConstruct = constructDmabufTextureBuilderModifier
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.modifier"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:modifier"
        })
#endif

-- VVV Prop "n-planes"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@n-planes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #nPlanes
-- @
getDmabufTextureBuilderNPlanes :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m Word32
getDmabufTextureBuilderNPlanes :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m Word32
getDmabufTextureBuilderNPlanes o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"n-planes"

-- | Set the value of the “@n-planes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #nPlanes 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderNPlanes :: (MonadIO m, IsDmabufTextureBuilder o) => o -> Word32 -> m ()
setDmabufTextureBuilderNPlanes :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> Word32 -> m ()
setDmabufTextureBuilderNPlanes o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"n-planes" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@n-planes@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderNPlanes :: (IsDmabufTextureBuilder o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDmabufTextureBuilderNPlanes :: forall o (m :: * -> *).
(IsDmabufTextureBuilder o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructDmabufTextureBuilderNPlanes Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"n-planes" Word32
val

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderNPlanesPropertyInfo
instance AttrInfo DmabufTextureBuilderNPlanesPropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderNPlanesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DmabufTextureBuilderNPlanesPropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderNPlanesPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint DmabufTextureBuilderNPlanesPropertyInfo = (~) Word32
    type AttrTransferType DmabufTextureBuilderNPlanesPropertyInfo = Word32
    type AttrGetType DmabufTextureBuilderNPlanesPropertyInfo = Word32
    type AttrLabel DmabufTextureBuilderNPlanesPropertyInfo = "n-planes"
    type AttrOrigin DmabufTextureBuilderNPlanesPropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderNPlanes
    attrSet = setDmabufTextureBuilderNPlanes
    attrTransfer _ v = do
        return v
    attrConstruct = constructDmabufTextureBuilderNPlanes
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.nPlanes"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:nPlanes"
        })
#endif

-- VVV Prop "premultiplied"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@premultiplied@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #premultiplied
-- @
getDmabufTextureBuilderPremultiplied :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m Bool
getDmabufTextureBuilderPremultiplied :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m Bool
getDmabufTextureBuilderPremultiplied o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"premultiplied"

-- | Set the value of the “@premultiplied@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #premultiplied 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderPremultiplied :: (MonadIO m, IsDmabufTextureBuilder o) => o -> Bool -> m ()
setDmabufTextureBuilderPremultiplied :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> Bool -> m ()
setDmabufTextureBuilderPremultiplied o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"premultiplied" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@premultiplied@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderPremultiplied :: (IsDmabufTextureBuilder o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDmabufTextureBuilderPremultiplied :: forall o (m :: * -> *).
(IsDmabufTextureBuilder o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDmabufTextureBuilderPremultiplied Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"premultiplied" Bool
val

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderPremultipliedPropertyInfo
instance AttrInfo DmabufTextureBuilderPremultipliedPropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderPremultipliedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DmabufTextureBuilderPremultipliedPropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderPremultipliedPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint DmabufTextureBuilderPremultipliedPropertyInfo = (~) Bool
    type AttrTransferType DmabufTextureBuilderPremultipliedPropertyInfo = Bool
    type AttrGetType DmabufTextureBuilderPremultipliedPropertyInfo = Bool
    type AttrLabel DmabufTextureBuilderPremultipliedPropertyInfo = "premultiplied"
    type AttrOrigin DmabufTextureBuilderPremultipliedPropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderPremultiplied
    attrSet = setDmabufTextureBuilderPremultiplied
    attrTransfer _ v = do
        return v
    attrConstruct = constructDmabufTextureBuilderPremultiplied
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.premultiplied"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:premultiplied"
        })
#endif

-- VVV Prop "update-region"
   -- Type: TInterface (Name {namespace = "cairo", name = "Region"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@update-region@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #updateRegion
-- @
getDmabufTextureBuilderUpdateRegion :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m (Maybe Cairo.Region.Region)
getDmabufTextureBuilderUpdateRegion :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m (Maybe Region)
getDmabufTextureBuilderUpdateRegion o
obj = IO (Maybe Region) -> m (Maybe Region)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Region) -> m (Maybe Region))
-> IO (Maybe Region) -> m (Maybe Region)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Region -> Region) -> IO (Maybe Region)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"update-region" ManagedPtr Region -> Region
Cairo.Region.Region

-- | Set the value of the “@update-region@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #updateRegion 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderUpdateRegion :: (MonadIO m, IsDmabufTextureBuilder o) => o -> Cairo.Region.Region -> m ()
setDmabufTextureBuilderUpdateRegion :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> Region -> m ()
setDmabufTextureBuilderUpdateRegion o
obj Region
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Region -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"update-region" (Region -> Maybe Region
forall a. a -> Maybe a
Just Region
val)

-- | Construct a `GValueConstruct` with valid value for the “@update-region@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderUpdateRegion :: (IsDmabufTextureBuilder o, MIO.MonadIO m) => Cairo.Region.Region -> m (GValueConstruct o)
constructDmabufTextureBuilderUpdateRegion :: forall o (m :: * -> *).
(IsDmabufTextureBuilder o, MonadIO m) =>
Region -> m (GValueConstruct o)
constructDmabufTextureBuilderUpdateRegion Region
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Region -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"update-region" (Region -> Maybe Region
forall a. a -> Maybe a
P.Just Region
val)

-- | Set the value of the “@update-region@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #updateRegion
-- @
clearDmabufTextureBuilderUpdateRegion :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m ()
clearDmabufTextureBuilderUpdateRegion :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m ()
clearDmabufTextureBuilderUpdateRegion o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Region -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"update-region" (Maybe Region
forall a. Maybe a
Nothing :: Maybe Cairo.Region.Region)

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderUpdateRegionPropertyInfo
instance AttrInfo DmabufTextureBuilderUpdateRegionPropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderUpdateRegionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DmabufTextureBuilderUpdateRegionPropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderUpdateRegionPropertyInfo = (~) Cairo.Region.Region
    type AttrTransferTypeConstraint DmabufTextureBuilderUpdateRegionPropertyInfo = (~) Cairo.Region.Region
    type AttrTransferType DmabufTextureBuilderUpdateRegionPropertyInfo = Cairo.Region.Region
    type AttrGetType DmabufTextureBuilderUpdateRegionPropertyInfo = (Maybe Cairo.Region.Region)
    type AttrLabel DmabufTextureBuilderUpdateRegionPropertyInfo = "update-region"
    type AttrOrigin DmabufTextureBuilderUpdateRegionPropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderUpdateRegion
    attrSet = setDmabufTextureBuilderUpdateRegion
    attrTransfer _ v = do
        return v
    attrConstruct = constructDmabufTextureBuilderUpdateRegion
    attrClear = clearDmabufTextureBuilderUpdateRegion
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.updateRegion"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:updateRegion"
        })
#endif

-- VVV Prop "update-texture"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Texture"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@update-texture@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #updateTexture
-- @
getDmabufTextureBuilderUpdateTexture :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m (Maybe Gdk.Texture.Texture)
getDmabufTextureBuilderUpdateTexture :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m (Maybe Texture)
getDmabufTextureBuilderUpdateTexture o
obj = IO (Maybe Texture) -> m (Maybe Texture)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Texture) -> m (Maybe Texture))
-> IO (Maybe Texture) -> m (Maybe Texture)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Texture -> Texture) -> IO (Maybe Texture)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"update-texture" ManagedPtr Texture -> Texture
Gdk.Texture.Texture

-- | Set the value of the “@update-texture@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #updateTexture 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderUpdateTexture :: (MonadIO m, IsDmabufTextureBuilder o, Gdk.Texture.IsTexture a) => o -> a -> m ()
setDmabufTextureBuilderUpdateTexture :: forall (m :: * -> *) o a.
(MonadIO m, IsDmabufTextureBuilder o, IsTexture a) =>
o -> a -> m ()
setDmabufTextureBuilderUpdateTexture o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"update-texture" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@update-texture@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderUpdateTexture :: (IsDmabufTextureBuilder o, MIO.MonadIO m, Gdk.Texture.IsTexture a) => a -> m (GValueConstruct o)
constructDmabufTextureBuilderUpdateTexture :: forall o (m :: * -> *) a.
(IsDmabufTextureBuilder o, MonadIO m, IsTexture a) =>
a -> m (GValueConstruct o)
constructDmabufTextureBuilderUpdateTexture a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"update-texture" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@update-texture@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #updateTexture
-- @
clearDmabufTextureBuilderUpdateTexture :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m ()
clearDmabufTextureBuilderUpdateTexture :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m ()
clearDmabufTextureBuilderUpdateTexture o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Texture -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"update-texture" (Maybe Texture
forall a. Maybe a
Nothing :: Maybe Gdk.Texture.Texture)

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderUpdateTexturePropertyInfo
instance AttrInfo DmabufTextureBuilderUpdateTexturePropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderUpdateTexturePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DmabufTextureBuilderUpdateTexturePropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderUpdateTexturePropertyInfo = Gdk.Texture.IsTexture
    type AttrTransferTypeConstraint DmabufTextureBuilderUpdateTexturePropertyInfo = Gdk.Texture.IsTexture
    type AttrTransferType DmabufTextureBuilderUpdateTexturePropertyInfo = Gdk.Texture.Texture
    type AttrGetType DmabufTextureBuilderUpdateTexturePropertyInfo = (Maybe Gdk.Texture.Texture)
    type AttrLabel DmabufTextureBuilderUpdateTexturePropertyInfo = "update-texture"
    type AttrOrigin DmabufTextureBuilderUpdateTexturePropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderUpdateTexture
    attrSet = setDmabufTextureBuilderUpdateTexture
    attrTransfer _ v = do
        unsafeCastTo Gdk.Texture.Texture v
    attrConstruct = constructDmabufTextureBuilderUpdateTexture
    attrClear = clearDmabufTextureBuilderUpdateTexture
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.updateTexture"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:updateTexture"
        })
#endif

-- VVV Prop "width"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dmabufTextureBuilder #width
-- @
getDmabufTextureBuilderWidth :: (MonadIO m, IsDmabufTextureBuilder o) => o -> m Word32
getDmabufTextureBuilderWidth :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> m Word32
getDmabufTextureBuilderWidth o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"width"

-- | Set the value of the “@width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dmabufTextureBuilder [ #width 'Data.GI.Base.Attributes.:=' value ]
-- @
setDmabufTextureBuilderWidth :: (MonadIO m, IsDmabufTextureBuilder o) => o -> Word32 -> m ()
setDmabufTextureBuilderWidth :: forall (m :: * -> *) o.
(MonadIO m, IsDmabufTextureBuilder o) =>
o -> Word32 -> m ()
setDmabufTextureBuilderWidth o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"width" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDmabufTextureBuilderWidth :: (IsDmabufTextureBuilder o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDmabufTextureBuilderWidth :: forall o (m :: * -> *).
(IsDmabufTextureBuilder o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructDmabufTextureBuilderWidth Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"width" Word32
val

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderWidthPropertyInfo
instance AttrInfo DmabufTextureBuilderWidthPropertyInfo where
    type AttrAllowedOps DmabufTextureBuilderWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DmabufTextureBuilderWidthPropertyInfo = IsDmabufTextureBuilder
    type AttrSetTypeConstraint DmabufTextureBuilderWidthPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint DmabufTextureBuilderWidthPropertyInfo = (~) Word32
    type AttrTransferType DmabufTextureBuilderWidthPropertyInfo = Word32
    type AttrGetType DmabufTextureBuilderWidthPropertyInfo = Word32
    type AttrLabel DmabufTextureBuilderWidthPropertyInfo = "width"
    type AttrOrigin DmabufTextureBuilderWidthPropertyInfo = DmabufTextureBuilder
    attrGet = getDmabufTextureBuilderWidth
    attrSet = setDmabufTextureBuilderWidth
    attrTransfer _ v = do
        return v
    attrConstruct = constructDmabufTextureBuilderWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.width"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#g:attr:width"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DmabufTextureBuilder
type instance O.AttributeList DmabufTextureBuilder = DmabufTextureBuilderAttributeList
type DmabufTextureBuilderAttributeList = ('[ '("display", DmabufTextureBuilderDisplayPropertyInfo), '("fourcc", DmabufTextureBuilderFourccPropertyInfo), '("height", DmabufTextureBuilderHeightPropertyInfo), '("modifier", DmabufTextureBuilderModifierPropertyInfo), '("nPlanes", DmabufTextureBuilderNPlanesPropertyInfo), '("premultiplied", DmabufTextureBuilderPremultipliedPropertyInfo), '("updateRegion", DmabufTextureBuilderUpdateRegionPropertyInfo), '("updateTexture", DmabufTextureBuilderUpdateTexturePropertyInfo), '("width", DmabufTextureBuilderWidthPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
dmabufTextureBuilderDisplay :: AttrLabelProxy "display"
dmabufTextureBuilderDisplay = AttrLabelProxy

dmabufTextureBuilderFourcc :: AttrLabelProxy "fourcc"
dmabufTextureBuilderFourcc = AttrLabelProxy

dmabufTextureBuilderHeight :: AttrLabelProxy "height"
dmabufTextureBuilderHeight = AttrLabelProxy

dmabufTextureBuilderModifier :: AttrLabelProxy "modifier"
dmabufTextureBuilderModifier = AttrLabelProxy

dmabufTextureBuilderNPlanes :: AttrLabelProxy "nPlanes"
dmabufTextureBuilderNPlanes = AttrLabelProxy

dmabufTextureBuilderPremultiplied :: AttrLabelProxy "premultiplied"
dmabufTextureBuilderPremultiplied = AttrLabelProxy

dmabufTextureBuilderUpdateRegion :: AttrLabelProxy "updateRegion"
dmabufTextureBuilderUpdateRegion = AttrLabelProxy

dmabufTextureBuilderUpdateTexture :: AttrLabelProxy "updateTexture"
dmabufTextureBuilderUpdateTexture = AttrLabelProxy

dmabufTextureBuilderWidth :: AttrLabelProxy "width"
dmabufTextureBuilderWidth = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DmabufTextureBuilder = DmabufTextureBuilderSignalList
type DmabufTextureBuilderSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method DmabufTextureBuilder::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gdk" , name = "DmabufTextureBuilder" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_new" gdk_dmabuf_texture_builder_new :: 
    IO (Ptr DmabufTextureBuilder)

-- | Creates a new texture builder.
-- 
-- /Since: 4.14/
dmabufTextureBuilderNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m DmabufTextureBuilder
    -- ^ __Returns:__ the new @GdkTextureBuilder@
dmabufTextureBuilderNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m DmabufTextureBuilder
dmabufTextureBuilderNew  = IO DmabufTextureBuilder -> m DmabufTextureBuilder
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DmabufTextureBuilder -> m DmabufTextureBuilder)
-> IO DmabufTextureBuilder -> m DmabufTextureBuilder
forall a b. (a -> b) -> a -> b
$ do
    result <- IO (Ptr DmabufTextureBuilder)
gdk_dmabuf_texture_builder_new
    checkUnexpectedReturnNULL "dmabufTextureBuilderNew" result
    result' <- (wrapObject DmabufTextureBuilder) result
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method DmabufTextureBuilder::build
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "destroy function to be called when the texture is\n  released"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to the destroy function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Texture" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_build" gdk_dmabuf_texture_builder_build :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    Ptr () ->                               -- data : TBasicType TPtr
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gdk.Texture.Texture)

-- | Builds a new @GdkTexture@ with the values set up in the builder.
-- 
-- It is a programming error to call this function if any mandatory
-- property has not been set.
-- 
-- If the dmabuf is not supported by GTK, 'P.Nothing' will be returned and /@error@/ will be set.
-- 
-- The @destroy@ function gets called when the returned texture gets released.
-- 
-- It is possible to call this function multiple times to create multiple textures,
-- possibly with changing properties in between.
-- 
-- It is the responsibility of the caller to keep the file descriptors for the planes
-- open until the created texture is no longer used, and close them afterwards (possibly
-- using the /@destroy@/ notify).
-- 
-- Not all formats defined in the @drm_fourcc.h@ header are supported. You can use
-- 'GI.Gdk.Objects.Display.displayGetDmabufFormats' to get a list of supported formats.
-- 
-- /Since: 4.14/
dmabufTextureBuilderBuild ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Maybe (GLib.Callbacks.DestroyNotify)
    -- ^ /@destroy@/: destroy function to be called when the texture is
    --   released
    -> Ptr ()
    -- ^ /@data@/: user data to pass to the destroy function
    -> m (Maybe Gdk.Texture.Texture)
    -- ^ __Returns:__ a newly built @GdkTexture@ or @NULL@
    --   if the format is not supported /(Can throw 'Data.GI.Base.GError.GError')/
dmabufTextureBuilderBuild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Maybe DestroyNotify -> Ptr () -> m (Maybe Texture)
dmabufTextureBuilderBuild a
self Maybe DestroyNotify
destroy Ptr ()
data_ = IO (Maybe Texture) -> m (Maybe Texture)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Texture) -> m (Maybe Texture))
-> IO (Maybe Texture) -> m (Maybe Texture)
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    maybeDestroy <- case destroy of
        Maybe DestroyNotify
Nothing -> FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr DestroyNotify
forall a. FunPtr a
FP.nullFunPtr
        Just DestroyNotify
jDestroy -> do
            ptrdestroy <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
            jDestroy' <- GLib.Callbacks.mk_DestroyNotify (GLib.Callbacks.wrap_DestroyNotify (Just ptrdestroy) jDestroy)
            poke ptrdestroy jDestroy'
            return jDestroy'
    onException (do
        result <- propagateGError $ gdk_dmabuf_texture_builder_build self' maybeDestroy data_
        maybeResult <- convertIfNonNull result $ \Ptr Texture
result' -> do
            result'' <- ((ManagedPtr Texture -> Texture) -> Ptr Texture -> IO Texture
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Texture -> Texture
Gdk.Texture.Texture) Ptr Texture
result'
            return result''
        touchManagedPtr self
        return maybeResult
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderBuildMethodInfo
instance (signature ~ (Maybe (GLib.Callbacks.DestroyNotify) -> Ptr () -> m (Maybe Gdk.Texture.Texture)), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderBuildMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderBuild

instance O.OverloadedMethodInfo DmabufTextureBuilderBuildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderBuild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderBuild"
        })


#endif

-- method DmabufTextureBuilder::get_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Display" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_display" gdk_dmabuf_texture_builder_get_display :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO (Ptr Gdk.Display.Display)

-- | Returns the display that this texture builder is
-- associated with.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a \`GdkDmabufTextureBuilder
    -> m Gdk.Display.Display
    -- ^ __Returns:__ the display
dmabufTextureBuilderGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m Display
dmabufTextureBuilderGetDisplay a
self = IO Display -> m Display
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Display -> m Display) -> IO Display -> m Display
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_display self'
    checkUnexpectedReturnNULL "dmabufTextureBuilderGetDisplay" result
    result' <- (newObject Gdk.Display.Display) result
    touchManagedPtr self
    return result'

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetDisplayMethodInfo
instance (signature ~ (m Gdk.Display.Display), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetDisplayMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetDisplay

instance O.OverloadedMethodInfo DmabufTextureBuilderGetDisplayMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetDisplay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetDisplay"
        })


#endif

-- method DmabufTextureBuilder::get_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "plane"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the plane to get the fd for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_fd" gdk_dmabuf_texture_builder_get_fd :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- plane : TBasicType TUInt
    IO Int32

-- | Gets the file descriptor for a plane.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@plane@/: the plane to get the fd for
    -> m Int32
    -- ^ __Returns:__ the file descriptor
dmabufTextureBuilderGetFd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> m Int32
dmabufTextureBuilderGetFd a
self Word32
plane = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_fd self' plane
    touchManagedPtr self
    return result

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetFdMethodInfo
instance (signature ~ (Word32 -> m Int32), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetFdMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetFd

instance O.OverloadedMethodInfo DmabufTextureBuilderGetFdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetFd",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetFd"
        })


#endif

-- method DmabufTextureBuilder::get_fourcc
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt32)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_fourcc" gdk_dmabuf_texture_builder_get_fourcc :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO Word32

-- | Gets the format previously set via 'GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetFourcc'
-- or 0 if the format wasn\'t set.
-- 
-- The format is specified as a fourcc code.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetFourcc ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> m Word32
    -- ^ __Returns:__ The format
dmabufTextureBuilderGetFourcc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m Word32
dmabufTextureBuilderGetFourcc a
self = IO Word32 -> m Word32
forall a. IO a -> m a
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
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_fourcc self'
    touchManagedPtr self
    return result

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetFourccMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetFourccMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetFourcc

instance O.OverloadedMethodInfo DmabufTextureBuilderGetFourccMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetFourcc",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetFourcc"
        })


#endif

-- method DmabufTextureBuilder::get_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_height" gdk_dmabuf_texture_builder_get_height :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO Word32

-- | Gets the height previously set via 'GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetHeight' or
-- 0 if the height wasn\'t set.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> m Word32
    -- ^ __Returns:__ The height
dmabufTextureBuilderGetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m Word32
dmabufTextureBuilderGetHeight a
self = IO Word32 -> m Word32
forall a. IO a -> m a
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
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_height self'
    touchManagedPtr self
    return result

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetHeightMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetHeightMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetHeight

instance O.OverloadedMethodInfo DmabufTextureBuilderGetHeightMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetHeight",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetHeight"
        })


#endif

-- method DmabufTextureBuilder::get_modifier
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_modifier" gdk_dmabuf_texture_builder_get_modifier :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO Word64

-- | Gets the modifier value.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetModifier ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> m Word64
    -- ^ __Returns:__ the modifier
dmabufTextureBuilderGetModifier :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m Word64
dmabufTextureBuilderGetModifier a
self = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_modifier self'
    touchManagedPtr self
    return result

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetModifierMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetModifierMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetModifier

instance O.OverloadedMethodInfo DmabufTextureBuilderGetModifierMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetModifier",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetModifier"
        })


#endif

-- method DmabufTextureBuilder::get_n_planes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_n_planes" gdk_dmabuf_texture_builder_get_n_planes :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO Word32

-- | Gets the number of planes.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetNPlanes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> m Word32
    -- ^ __Returns:__ The number of planes
dmabufTextureBuilderGetNPlanes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m Word32
dmabufTextureBuilderGetNPlanes a
self = IO Word32 -> m Word32
forall a. IO a -> m a
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
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_n_planes self'
    touchManagedPtr self
    return result

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetNPlanesMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetNPlanesMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetNPlanes

instance O.OverloadedMethodInfo DmabufTextureBuilderGetNPlanesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetNPlanes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetNPlanes"
        })


#endif

-- method DmabufTextureBuilder::get_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "plane"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the plane to get the offset for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_offset" gdk_dmabuf_texture_builder_get_offset :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- plane : TBasicType TUInt
    IO Word32

-- | Gets the offset value for a plane.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@plane@/: the plane to get the offset for
    -> m Word32
    -- ^ __Returns:__ the offset
dmabufTextureBuilderGetOffset :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> m Word32
dmabufTextureBuilderGetOffset a
self Word32
plane = IO Word32 -> m Word32
forall a. IO a -> m a
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
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_offset self' plane
    touchManagedPtr self
    return result

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetOffsetMethodInfo
instance (signature ~ (Word32 -> m Word32), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetOffsetMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetOffset

instance O.OverloadedMethodInfo DmabufTextureBuilderGetOffsetMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetOffset",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetOffset"
        })


#endif

-- method DmabufTextureBuilder::get_premultiplied
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_premultiplied" gdk_dmabuf_texture_builder_get_premultiplied :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO CInt

-- | Whether the data is premultiplied.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetPremultiplied ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> m Bool
    -- ^ __Returns:__ whether the data is premultiplied
dmabufTextureBuilderGetPremultiplied :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m Bool
dmabufTextureBuilderGetPremultiplied a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_premultiplied self'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr self
    return result'

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetPremultipliedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetPremultipliedMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetPremultiplied

instance O.OverloadedMethodInfo DmabufTextureBuilderGetPremultipliedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetPremultiplied",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetPremultiplied"
        })


#endif

-- method DmabufTextureBuilder::get_stride
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "plane"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the plane to get the stride for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_stride" gdk_dmabuf_texture_builder_get_stride :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- plane : TBasicType TUInt
    IO Word32

-- | Gets the stride value for a plane.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetStride ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@plane@/: the plane to get the stride for
    -> m Word32
    -- ^ __Returns:__ the stride
dmabufTextureBuilderGetStride :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> m Word32
dmabufTextureBuilderGetStride a
self Word32
plane = IO Word32 -> m Word32
forall a. IO a -> m a
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
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_stride self' plane
    touchManagedPtr self
    return result

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetStrideMethodInfo
instance (signature ~ (Word32 -> m Word32), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetStrideMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetStride

instance O.OverloadedMethodInfo DmabufTextureBuilderGetStrideMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetStride",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetStride"
        })


#endif

-- method DmabufTextureBuilder::get_update_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "cairo" , name = "Region" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_update_region" gdk_dmabuf_texture_builder_get_update_region :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO (Ptr Cairo.Region.Region)

-- | Gets the region previously set via 'GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetUpdateRegion' or
-- 'P.Nothing' if none was set.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetUpdateRegion ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> m (Maybe Cairo.Region.Region)
    -- ^ __Returns:__ The region
dmabufTextureBuilderGetUpdateRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m (Maybe Region)
dmabufTextureBuilderGetUpdateRegion a
self = IO (Maybe Region) -> m (Maybe Region)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Region) -> m (Maybe Region))
-> IO (Maybe Region) -> m (Maybe Region)
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_update_region self'
    maybeResult <- convertIfNonNull result $ \Ptr Region
result' -> do
        result'' <- ((ManagedPtr Region -> Region) -> Ptr Region -> IO Region
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Region -> Region
Cairo.Region.Region) Ptr Region
result'
        return result''
    touchManagedPtr self
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetUpdateRegionMethodInfo
instance (signature ~ (m (Maybe Cairo.Region.Region)), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetUpdateRegionMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetUpdateRegion

instance O.OverloadedMethodInfo DmabufTextureBuilderGetUpdateRegionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetUpdateRegion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetUpdateRegion"
        })


#endif

-- method DmabufTextureBuilder::get_update_texture
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Texture" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_update_texture" gdk_dmabuf_texture_builder_get_update_texture :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO (Ptr Gdk.Texture.Texture)

-- | Gets the texture previously set via 'GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetUpdateTexture' or
-- 'P.Nothing' if none was set.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetUpdateTexture ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> m (Maybe Gdk.Texture.Texture)
    -- ^ __Returns:__ The texture
dmabufTextureBuilderGetUpdateTexture :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m (Maybe Texture)
dmabufTextureBuilderGetUpdateTexture a
self = IO (Maybe Texture) -> m (Maybe Texture)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Texture) -> m (Maybe Texture))
-> IO (Maybe Texture) -> m (Maybe Texture)
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_update_texture self'
    maybeResult <- convertIfNonNull result $ \Ptr Texture
result' -> do
        result'' <- ((ManagedPtr Texture -> Texture) -> Ptr Texture -> IO Texture
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Texture -> Texture
Gdk.Texture.Texture) Ptr Texture
result'
        return result''
    touchManagedPtr self
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetUpdateTextureMethodInfo
instance (signature ~ (m (Maybe Gdk.Texture.Texture)), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetUpdateTextureMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetUpdateTexture

instance O.OverloadedMethodInfo DmabufTextureBuilderGetUpdateTextureMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetUpdateTexture",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetUpdateTexture"
        })


#endif

-- method DmabufTextureBuilder::get_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_get_width" gdk_dmabuf_texture_builder_get_width :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    IO Word32

-- | Gets the width previously set via 'GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetWidth' or
-- 0 if the width wasn\'t set.
-- 
-- /Since: 4.14/
dmabufTextureBuilderGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> m Word32
    -- ^ __Returns:__ The width
dmabufTextureBuilderGetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> m Word32
dmabufTextureBuilderGetWidth a
self = IO Word32 -> m Word32
forall a. IO a -> m a
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
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gdk_dmabuf_texture_builder_get_width self'
    touchManagedPtr self
    return result

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderGetWidthMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderGetWidthMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderGetWidth

instance O.OverloadedMethodInfo DmabufTextureBuilderGetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderGetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderGetWidth"
        })


#endif

-- method DmabufTextureBuilder::set_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the display" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_display" gdk_dmabuf_texture_builder_set_display :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO ()

-- | Sets the display that this texture builder is
-- associated with.
-- 
-- The display is used to determine the supported
-- dma-buf formats.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a, Gdk.Display.IsDisplay b) =>
    a
    -- ^ /@self@/: a \`GdkDmabufTextureBuilder
    -> b
    -- ^ /@display@/: the display
    -> m ()
dmabufTextureBuilderSetDisplay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a, IsDisplay b) =>
a -> b -> m ()
dmabufTextureBuilderSetDisplay a
self b
display = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    display' <- unsafeManagedPtrCastPtr display
    gdk_dmabuf_texture_builder_set_display self' display'
    touchManagedPtr self
    touchManagedPtr display
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetDisplayMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDmabufTextureBuilder a, Gdk.Display.IsDisplay b) => O.OverloadedMethod DmabufTextureBuilderSetDisplayMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetDisplay

instance O.OverloadedMethodInfo DmabufTextureBuilderSetDisplayMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetDisplay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetDisplay"
        })


#endif

-- method DmabufTextureBuilder::set_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "plane"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the plane to set the fd for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file descriptor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_fd" gdk_dmabuf_texture_builder_set_fd :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- plane : TBasicType TUInt
    Int32 ->                                -- fd : TBasicType TInt
    IO ()

-- | Sets the file descriptor for a plane.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@plane@/: the plane to set the fd for
    -> Int32
    -- ^ /@fd@/: the file descriptor
    -> m ()
dmabufTextureBuilderSetFd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> Int32 -> m ()
dmabufTextureBuilderSetFd a
self Word32
plane Int32
fd = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    gdk_dmabuf_texture_builder_set_fd self' plane fd
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetFdMethodInfo
instance (signature ~ (Word32 -> Int32 -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetFdMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetFd

instance O.OverloadedMethodInfo DmabufTextureBuilderSetFdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetFd",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetFd"
        })


#endif

-- method DmabufTextureBuilder::set_fourcc
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fourcc"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the texture's format or 0 to unset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_fourcc" gdk_dmabuf_texture_builder_set_fourcc :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- fourcc : TBasicType TUInt32
    IO ()

-- | Sets the format of the texture.
-- 
-- The format is specified as a fourcc code.
-- 
-- The format must be set before calling 'GI.Gdk.Objects.GLTextureBuilder.gLTextureBuilderBuild'.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetFourcc ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@fourcc@/: the texture\'s format or 0 to unset
    -> m ()
dmabufTextureBuilderSetFourcc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> m ()
dmabufTextureBuilderSetFourcc a
self Word32
fourcc = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    gdk_dmabuf_texture_builder_set_fourcc self' fourcc
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetFourccMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetFourccMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetFourcc

instance O.OverloadedMethodInfo DmabufTextureBuilderSetFourccMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetFourcc",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetFourcc"
        })


#endif

-- method DmabufTextureBuilder::set_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the texture's height or 0 to unset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_height" gdk_dmabuf_texture_builder_set_height :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- height : TBasicType TUInt
    IO ()

-- | Sets the height of the texture.
-- 
-- The height must be set before calling 'GI.Gdk.Objects.GLTextureBuilder.gLTextureBuilderBuild'.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@height@/: the texture\'s height or 0 to unset
    -> m ()
dmabufTextureBuilderSetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> m ()
dmabufTextureBuilderSetHeight a
self Word32
height = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    gdk_dmabuf_texture_builder_set_height self' height
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetHeightMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetHeightMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetHeight

instance O.OverloadedMethodInfo DmabufTextureBuilderSetHeightMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetHeight",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetHeight"
        })


#endif

-- method DmabufTextureBuilder::set_modifier
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "modifier"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the modifier value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_modifier" gdk_dmabuf_texture_builder_set_modifier :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word64 ->                               -- modifier : TBasicType TUInt64
    IO ()

-- | Sets the modifier.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetModifier ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word64
    -- ^ /@modifier@/: the modifier value
    -> m ()
dmabufTextureBuilderSetModifier :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word64 -> m ()
dmabufTextureBuilderSetModifier a
self Word64
modifier = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    gdk_dmabuf_texture_builder_set_modifier self' modifier
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetModifierMethodInfo
instance (signature ~ (Word64 -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetModifierMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetModifier

instance O.OverloadedMethodInfo DmabufTextureBuilderSetModifierMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetModifier",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetModifier"
        })


#endif

-- method DmabufTextureBuilder::set_n_planes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_planes"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of planes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_n_planes" gdk_dmabuf_texture_builder_set_n_planes :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- n_planes : TBasicType TUInt
    IO ()

-- | Sets the number of planes of the texture.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetNPlanes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@nPlanes@/: the number of planes
    -> m ()
dmabufTextureBuilderSetNPlanes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> m ()
dmabufTextureBuilderSetNPlanes a
self Word32
nPlanes = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    gdk_dmabuf_texture_builder_set_n_planes self' nPlanes
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetNPlanesMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetNPlanesMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetNPlanes

instance O.OverloadedMethodInfo DmabufTextureBuilderSetNPlanesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetNPlanes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetNPlanes"
        })


#endif

-- method DmabufTextureBuilder::set_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "plane"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the plane to set the offset for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the offset value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_offset" gdk_dmabuf_texture_builder_set_offset :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- plane : TBasicType TUInt
    Word32 ->                               -- offset : TBasicType TUInt
    IO ()

-- | Sets the offset for a plane.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@plane@/: the plane to set the offset for
    -> Word32
    -- ^ /@offset@/: the offset value
    -> m ()
dmabufTextureBuilderSetOffset :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> Word32 -> m ()
dmabufTextureBuilderSetOffset a
self Word32
plane Word32
offset = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    gdk_dmabuf_texture_builder_set_offset self' plane offset
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetOffsetMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetOffsetMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetOffset

instance O.OverloadedMethodInfo DmabufTextureBuilderSetOffsetMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetOffset",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetOffset"
        })


#endif

-- method DmabufTextureBuilder::set_premultiplied
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "premultiplied"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the data is premultiplied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_premultiplied" gdk_dmabuf_texture_builder_set_premultiplied :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    CInt ->                                 -- premultiplied : TBasicType TBoolean
    IO ()

-- | Sets whether the data is premultiplied.
-- 
-- Unless otherwise specified, all formats including alpha channels are assumed
-- to be premultiplied.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetPremultiplied ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Bool
    -- ^ /@premultiplied@/: whether the data is premultiplied
    -> m ()
dmabufTextureBuilderSetPremultiplied :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Bool -> m ()
dmabufTextureBuilderSetPremultiplied a
self Bool
premultiplied = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let premultiplied' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
premultiplied
    gdk_dmabuf_texture_builder_set_premultiplied self' premultiplied'
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetPremultipliedMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetPremultipliedMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetPremultiplied

instance O.OverloadedMethodInfo DmabufTextureBuilderSetPremultipliedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetPremultiplied",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetPremultiplied"
        })


#endif

-- method DmabufTextureBuilder::set_stride
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "plane"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the plane to set the stride for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stride"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the stride value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_stride" gdk_dmabuf_texture_builder_set_stride :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- plane : TBasicType TUInt
    Word32 ->                               -- stride : TBasicType TUInt
    IO ()

-- | Sets the stride for a plane.
-- 
-- The stride must be set for all planes before calling 'GI.Gdk.Objects.GLTextureBuilder.gLTextureBuilderBuild'.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetStride ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@plane@/: the plane to set the stride for
    -> Word32
    -- ^ /@stride@/: the stride value
    -> m ()
dmabufTextureBuilderSetStride :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> Word32 -> m ()
dmabufTextureBuilderSetStride a
self Word32
plane Word32
stride = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    gdk_dmabuf_texture_builder_set_stride self' plane stride
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetStrideMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetStrideMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetStride

instance O.OverloadedMethodInfo DmabufTextureBuilderSetStrideMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetStride",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetStride"
        })


#endif

-- method DmabufTextureBuilder::set_update_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "region"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Region" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the region to update"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_update_region" gdk_dmabuf_texture_builder_set_update_region :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Ptr Cairo.Region.Region ->              -- region : TInterface (Name {namespace = "cairo", name = "Region"})
    IO ()

-- | Sets the region to be updated by this texture. Together with
-- [DmabufTextureBuilder:updateTexture]("GI.Gdk.Objects.DmabufTextureBuilder#g:attr:updateTexture") this describes an
-- update of a previous texture.
-- 
-- When rendering animations of large textures, it is possible that
-- consecutive textures are only updating contents in parts of the texture.
-- It is then possible to describe this update via these two properties,
-- so that GTK can avoid rerendering parts that did not change.
-- 
-- An example would be a screen recording where only the mouse pointer moves.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetUpdateRegion ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Maybe (Cairo.Region.Region)
    -- ^ /@region@/: the region to update
    -> m ()
dmabufTextureBuilderSetUpdateRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Maybe Region -> m ()
dmabufTextureBuilderSetUpdateRegion a
self Maybe Region
region = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    maybeRegion <- case region of
        Maybe Region
Nothing -> Ptr Region -> IO (Ptr Region)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Region
forall a. Ptr a
FP.nullPtr
        Just Region
jRegion -> do
            jRegion' <- Region -> IO (Ptr Region)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Region
jRegion
            return jRegion'
    gdk_dmabuf_texture_builder_set_update_region self' maybeRegion
    touchManagedPtr self
    whenJust region touchManagedPtr
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetUpdateRegionMethodInfo
instance (signature ~ (Maybe (Cairo.Region.Region) -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetUpdateRegionMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetUpdateRegion

instance O.OverloadedMethodInfo DmabufTextureBuilderSetUpdateRegionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetUpdateRegion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetUpdateRegion"
        })


#endif

-- method DmabufTextureBuilder::set_update_texture
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "texture"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Texture" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the texture to update"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_update_texture" gdk_dmabuf_texture_builder_set_update_texture :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Ptr Gdk.Texture.Texture ->              -- texture : TInterface (Name {namespace = "Gdk", name = "Texture"})
    IO ()

-- | Sets the texture to be updated by this texture. See
-- 'GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetUpdateRegion' for an explanation.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetUpdateTexture ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a, Gdk.Texture.IsTexture b) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Maybe (b)
    -- ^ /@texture@/: the texture to update
    -> m ()
dmabufTextureBuilderSetUpdateTexture :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a, IsTexture b) =>
a -> Maybe b -> m ()
dmabufTextureBuilderSetUpdateTexture a
self Maybe b
texture = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    maybeTexture <- case texture of
        Maybe b
Nothing -> Ptr Texture -> IO (Ptr Texture)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Texture
forall a. Ptr a
FP.nullPtr
        Just b
jTexture -> do
            jTexture' <- b -> IO (Ptr Texture)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jTexture
            return jTexture'
    gdk_dmabuf_texture_builder_set_update_texture self' maybeTexture
    touchManagedPtr self
    whenJust texture touchManagedPtr
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetUpdateTextureMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDmabufTextureBuilder a, Gdk.Texture.IsTexture b) => O.OverloadedMethod DmabufTextureBuilderSetUpdateTextureMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetUpdateTexture

instance O.OverloadedMethodInfo DmabufTextureBuilderSetUpdateTextureMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetUpdateTexture",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetUpdateTexture"
        })


#endif

-- method DmabufTextureBuilder::set_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "DmabufTextureBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDmabufTextureBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The texture's width or 0 to unset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_dmabuf_texture_builder_set_width" gdk_dmabuf_texture_builder_set_width :: 
    Ptr DmabufTextureBuilder ->             -- self : TInterface (Name {namespace = "Gdk", name = "DmabufTextureBuilder"})
    Word32 ->                               -- width : TBasicType TUInt
    IO ()

-- | Sets the width of the texture.
-- 
-- The width must be set before calling 'GI.Gdk.Objects.GLTextureBuilder.gLTextureBuilderBuild'.
-- 
-- /Since: 4.14/
dmabufTextureBuilderSetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
    a
    -- ^ /@self@/: a @GdkDmabufTextureBuilder@
    -> Word32
    -- ^ /@width@/: The texture\'s width or 0 to unset
    -> m ()
dmabufTextureBuilderSetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDmabufTextureBuilder a) =>
a -> Word32 -> m ()
dmabufTextureBuilderSetWidth a
self Word32
width = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr DmabufTextureBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    gdk_dmabuf_texture_builder_set_width self' width
    touchManagedPtr self
    return ()

#if defined(ENABLE_OVERLOADING)
data DmabufTextureBuilderSetWidthMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDmabufTextureBuilder a) => O.OverloadedMethod DmabufTextureBuilderSetWidthMethodInfo a signature where
    overloadedMethod = dmabufTextureBuilderSetWidth

instance O.OverloadedMethodInfo DmabufTextureBuilderSetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.DmabufTextureBuilder.dmabufTextureBuilderSetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-DmabufTextureBuilder.html#v:dmabufTextureBuilderSetWidth"
        })


#endif