{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gdk.Objects.Surface.Surface' is a (usually) rectangular region on the screen.
-- It’s a low-level object, used to implement high-level objects
-- such as @/GtkWindow/@ or @/GtkDialog/@ in GTK.
-- 
-- The surfaces you see in practice are either t'GI.Gdk.Interfaces.Toplevel.Toplevel' or
-- t'GI.Gdk.Interfaces.Popup.Popup', and those interfaces provide much of the required
-- API to interact with these surfaces. Other, more specialized
-- surface types exist, but you will rarely interact with them
-- directly.

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

module GI.Gdk.Objects.Surface
    ( 

-- * Exported types
    Surface(..)                             ,
    IsSurface                               ,
    toSurface                               ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [beep]("GI.Gdk.Objects.Surface#g:method:beep"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [createCairoContext]("GI.Gdk.Objects.Surface#g:method:createCairoContext"), [createGlContext]("GI.Gdk.Objects.Surface#g:method:createGlContext"), [createSimilarSurface]("GI.Gdk.Objects.Surface#g:method:createSimilarSurface"), [createVulkanContext]("GI.Gdk.Objects.Surface#g:method:createVulkanContext"), [destroy]("GI.Gdk.Objects.Surface#g:method:destroy"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hide]("GI.Gdk.Objects.Surface#g:method:hide"), [isDestroyed]("GI.Gdk.Objects.Surface#g:method:isDestroyed"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [queueRender]("GI.Gdk.Objects.Surface#g:method:queueRender"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [requestLayout]("GI.Gdk.Objects.Surface#g:method:requestLayout"), [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"), [translateCoordinates]("GI.Gdk.Objects.Surface#g:method:translateCoordinates"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCursor]("GI.Gdk.Objects.Surface#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDeviceCursor]("GI.Gdk.Objects.Surface#g:method:getDeviceCursor"), [getDevicePosition]("GI.Gdk.Objects.Surface#g:method:getDevicePosition"), [getDisplay]("GI.Gdk.Objects.Surface#g:method:getDisplay"), [getFrameClock]("GI.Gdk.Objects.Surface#g:method:getFrameClock"), [getHeight]("GI.Gdk.Objects.Surface#g:method:getHeight"), [getMapped]("GI.Gdk.Objects.Surface#g:method:getMapped"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getScaleFactor]("GI.Gdk.Objects.Surface#g:method:getScaleFactor"), [getWidth]("GI.Gdk.Objects.Surface#g:method:getWidth").
-- 
-- ==== Setters
-- [setCursor]("GI.Gdk.Objects.Surface#g:method:setCursor"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDeviceCursor]("GI.Gdk.Objects.Surface#g:method:setDeviceCursor"), [setInputRegion]("GI.Gdk.Objects.Surface#g:method:setInputRegion"), [setOpaqueRegion]("GI.Gdk.Objects.Surface#g:method:setOpaqueRegion"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveSurfaceMethod                    ,
#endif

-- ** beep #method:beep#

#if defined(ENABLE_OVERLOADING)
    SurfaceBeepMethodInfo                   ,
#endif
    surfaceBeep                             ,


-- ** createCairoContext #method:createCairoContext#

#if defined(ENABLE_OVERLOADING)
    SurfaceCreateCairoContextMethodInfo     ,
#endif
    surfaceCreateCairoContext               ,


-- ** createGlContext #method:createGlContext#

#if defined(ENABLE_OVERLOADING)
    SurfaceCreateGlContextMethodInfo        ,
#endif
    surfaceCreateGlContext                  ,


-- ** createSimilarSurface #method:createSimilarSurface#

#if defined(ENABLE_OVERLOADING)
    SurfaceCreateSimilarSurfaceMethodInfo   ,
#endif
    surfaceCreateSimilarSurface             ,


-- ** createVulkanContext #method:createVulkanContext#

#if defined(ENABLE_OVERLOADING)
    SurfaceCreateVulkanContextMethodInfo    ,
#endif
    surfaceCreateVulkanContext              ,


-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING)
    SurfaceDestroyMethodInfo                ,
#endif
    surfaceDestroy                          ,


-- ** getCursor #method:getCursor#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetCursorMethodInfo              ,
#endif
    surfaceGetCursor                        ,


-- ** getDeviceCursor #method:getDeviceCursor#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetDeviceCursorMethodInfo        ,
#endif
    surfaceGetDeviceCursor                  ,


-- ** getDevicePosition #method:getDevicePosition#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetDevicePositionMethodInfo      ,
#endif
    surfaceGetDevicePosition                ,


-- ** getDisplay #method:getDisplay#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetDisplayMethodInfo             ,
#endif
    surfaceGetDisplay                       ,


-- ** getFrameClock #method:getFrameClock#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetFrameClockMethodInfo          ,
#endif
    surfaceGetFrameClock                    ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetHeightMethodInfo              ,
#endif
    surfaceGetHeight                        ,


-- ** getMapped #method:getMapped#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetMappedMethodInfo              ,
#endif
    surfaceGetMapped                        ,


-- ** getScaleFactor #method:getScaleFactor#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetScaleFactorMethodInfo         ,
#endif
    surfaceGetScaleFactor                   ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    SurfaceGetWidthMethodInfo               ,
#endif
    surfaceGetWidth                         ,


-- ** hide #method:hide#

#if defined(ENABLE_OVERLOADING)
    SurfaceHideMethodInfo                   ,
#endif
    surfaceHide                             ,


-- ** isDestroyed #method:isDestroyed#

#if defined(ENABLE_OVERLOADING)
    SurfaceIsDestroyedMethodInfo            ,
#endif
    surfaceIsDestroyed                      ,


-- ** newPopup #method:newPopup#

    surfaceNewPopup                         ,


-- ** newToplevel #method:newToplevel#

    surfaceNewToplevel                      ,


-- ** queueRender #method:queueRender#

#if defined(ENABLE_OVERLOADING)
    SurfaceQueueRenderMethodInfo            ,
#endif
    surfaceQueueRender                      ,


-- ** requestLayout #method:requestLayout#

#if defined(ENABLE_OVERLOADING)
    SurfaceRequestLayoutMethodInfo          ,
#endif
    surfaceRequestLayout                    ,


-- ** setCursor #method:setCursor#

#if defined(ENABLE_OVERLOADING)
    SurfaceSetCursorMethodInfo              ,
#endif
    surfaceSetCursor                        ,


-- ** setDeviceCursor #method:setDeviceCursor#

#if defined(ENABLE_OVERLOADING)
    SurfaceSetDeviceCursorMethodInfo        ,
#endif
    surfaceSetDeviceCursor                  ,


-- ** setInputRegion #method:setInputRegion#

#if defined(ENABLE_OVERLOADING)
    SurfaceSetInputRegionMethodInfo         ,
#endif
    surfaceSetInputRegion                   ,


-- ** setOpaqueRegion #method:setOpaqueRegion#

#if defined(ENABLE_OVERLOADING)
    SurfaceSetOpaqueRegionMethodInfo        ,
#endif
    surfaceSetOpaqueRegion                  ,


-- ** translateCoordinates #method:translateCoordinates#

#if defined(ENABLE_OVERLOADING)
    SurfaceTranslateCoordinatesMethodInfo   ,
#endif
    surfaceTranslateCoordinates             ,




 -- * Properties


-- ** cursor #attr:cursor#
-- | The mouse pointer for a t'GI.Gdk.Objects.Surface.Surface'. See 'GI.Gdk.Objects.Surface.surfaceSetCursor' and
-- 'GI.Gdk.Objects.Surface.surfaceGetCursor' for details.

#if defined(ENABLE_OVERLOADING)
    SurfaceCursorPropertyInfo               ,
#endif
    clearSurfaceCursor                      ,
    constructSurfaceCursor                  ,
    getSurfaceCursor                        ,
    setSurfaceCursor                        ,
#if defined(ENABLE_OVERLOADING)
    surfaceCursor                           ,
#endif


-- ** display #attr:display#
-- | The t'GI.Gdk.Objects.Display.Display' connection of the surface. See 'GI.Gdk.Objects.Surface.surfaceGetDisplay'
-- for details.

#if defined(ENABLE_OVERLOADING)
    SurfaceDisplayPropertyInfo              ,
#endif
    constructSurfaceDisplay                 ,
    getSurfaceDisplay                       ,
#if defined(ENABLE_OVERLOADING)
    surfaceDisplay                          ,
#endif


-- ** frameClock #attr:frameClock#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SurfaceFrameClockPropertyInfo           ,
#endif
    constructSurfaceFrameClock              ,
    getSurfaceFrameClock                    ,
#if defined(ENABLE_OVERLOADING)
    surfaceFrameClock                       ,
#endif


-- ** height #attr:height#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SurfaceHeightPropertyInfo               ,
#endif
    getSurfaceHeight                        ,
#if defined(ENABLE_OVERLOADING)
    surfaceHeight                           ,
#endif


-- ** mapped #attr:mapped#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SurfaceMappedPropertyInfo               ,
#endif
    getSurfaceMapped                        ,
#if defined(ENABLE_OVERLOADING)
    surfaceMapped                           ,
#endif


-- ** scaleFactor #attr:scaleFactor#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SurfaceScaleFactorPropertyInfo          ,
#endif
    getSurfaceScaleFactor                   ,
#if defined(ENABLE_OVERLOADING)
    surfaceScaleFactor                      ,
#endif


-- ** width #attr:width#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SurfaceWidthPropertyInfo                ,
#endif
    getSurfaceWidth                         ,
#if defined(ENABLE_OVERLOADING)
    surfaceWidth                            ,
#endif




 -- * Signals


-- ** enterMonitor #signal:enterMonitor#

    C_SurfaceEnterMonitorCallback           ,
    SurfaceEnterMonitorCallback             ,
#if defined(ENABLE_OVERLOADING)
    SurfaceEnterMonitorSignalInfo           ,
#endif
    afterSurfaceEnterMonitor                ,
    genClosure_SurfaceEnterMonitor          ,
    mk_SurfaceEnterMonitorCallback          ,
    noSurfaceEnterMonitorCallback           ,
    onSurfaceEnterMonitor                   ,
    wrap_SurfaceEnterMonitorCallback        ,


-- ** event #signal:event#

    C_SurfaceEventCallback                  ,
    SurfaceEventCallback                    ,
#if defined(ENABLE_OVERLOADING)
    SurfaceEventSignalInfo                  ,
#endif
    afterSurfaceEvent                       ,
    genClosure_SurfaceEvent                 ,
    mk_SurfaceEventCallback                 ,
    noSurfaceEventCallback                  ,
    onSurfaceEvent                          ,
    wrap_SurfaceEventCallback               ,


-- ** layout #signal:layout#

    C_SurfaceLayoutCallback                 ,
    SurfaceLayoutCallback                   ,
#if defined(ENABLE_OVERLOADING)
    SurfaceLayoutSignalInfo                 ,
#endif
    afterSurfaceLayout                      ,
    genClosure_SurfaceLayout                ,
    mk_SurfaceLayoutCallback                ,
    noSurfaceLayoutCallback                 ,
    onSurfaceLayout                         ,
    wrap_SurfaceLayoutCallback              ,


-- ** leaveMonitor #signal:leaveMonitor#

    C_SurfaceLeaveMonitorCallback           ,
    SurfaceLeaveMonitorCallback             ,
#if defined(ENABLE_OVERLOADING)
    SurfaceLeaveMonitorSignalInfo           ,
#endif
    afterSurfaceLeaveMonitor                ,
    genClosure_SurfaceLeaveMonitor          ,
    mk_SurfaceLeaveMonitorCallback          ,
    noSurfaceLeaveMonitorCallback           ,
    onSurfaceLeaveMonitor                   ,
    wrap_SurfaceLeaveMonitorCallback        ,


-- ** render #signal:render#

    C_SurfaceRenderCallback                 ,
    SurfaceRenderCallback                   ,
#if defined(ENABLE_OVERLOADING)
    SurfaceRenderSignalInfo                 ,
#endif
    afterSurfaceRender                      ,
    genClosure_SurfaceRender                ,
    mk_SurfaceRenderCallback                ,
    noSurfaceRenderCallback                 ,
    onSurfaceRender                         ,
    wrap_SurfaceRenderCallback              ,




    ) 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.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.CairoContext as Gdk.CairoContext
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.Display as Gdk.Display
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.VulkanContext as Gdk.VulkanContext

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

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

foreign import ccall "gdk_surface_get_type"
    c_gdk_surface_get_type :: IO B.Types.GType

instance B.Types.TypedObject Surface where
    glibType :: IO GType
glibType = IO GType
c_gdk_surface_get_type

instance B.Types.GObject Surface

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

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

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

-- | Convert 'Surface' 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 Surface) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_surface_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Surface -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Surface
P.Nothing = Ptr GValue -> Ptr Surface -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Surface
forall a. Ptr a
FP.nullPtr :: FP.Ptr Surface)
    gvalueSet_ Ptr GValue
gv (P.Just Surface
obj) = Surface -> (Ptr Surface -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Surface
obj (Ptr GValue -> Ptr Surface -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Surface)
gvalueGet_ Ptr GValue
gv = do
        Ptr Surface
ptr <- Ptr GValue -> IO (Ptr Surface)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Surface)
        if Ptr Surface
ptr Ptr Surface -> Ptr Surface -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Surface
forall a. Ptr a
FP.nullPtr
        then Surface -> Maybe Surface
forall a. a -> Maybe a
P.Just (Surface -> Maybe Surface) -> IO Surface -> IO (Maybe Surface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Surface -> Surface
Surface Ptr Surface
ptr
        else Maybe Surface -> IO (Maybe Surface)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Surface
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveSurfaceMethod (t :: Symbol) (o :: *) :: * where
    ResolveSurfaceMethod "beep" o = SurfaceBeepMethodInfo
    ResolveSurfaceMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSurfaceMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSurfaceMethod "createCairoContext" o = SurfaceCreateCairoContextMethodInfo
    ResolveSurfaceMethod "createGlContext" o = SurfaceCreateGlContextMethodInfo
    ResolveSurfaceMethod "createSimilarSurface" o = SurfaceCreateSimilarSurfaceMethodInfo
    ResolveSurfaceMethod "createVulkanContext" o = SurfaceCreateVulkanContextMethodInfo
    ResolveSurfaceMethod "destroy" o = SurfaceDestroyMethodInfo
    ResolveSurfaceMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSurfaceMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSurfaceMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSurfaceMethod "hide" o = SurfaceHideMethodInfo
    ResolveSurfaceMethod "isDestroyed" o = SurfaceIsDestroyedMethodInfo
    ResolveSurfaceMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSurfaceMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSurfaceMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSurfaceMethod "queueRender" o = SurfaceQueueRenderMethodInfo
    ResolveSurfaceMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSurfaceMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSurfaceMethod "requestLayout" o = SurfaceRequestLayoutMethodInfo
    ResolveSurfaceMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSurfaceMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSurfaceMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSurfaceMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSurfaceMethod "translateCoordinates" o = SurfaceTranslateCoordinatesMethodInfo
    ResolveSurfaceMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSurfaceMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSurfaceMethod "getCursor" o = SurfaceGetCursorMethodInfo
    ResolveSurfaceMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSurfaceMethod "getDeviceCursor" o = SurfaceGetDeviceCursorMethodInfo
    ResolveSurfaceMethod "getDevicePosition" o = SurfaceGetDevicePositionMethodInfo
    ResolveSurfaceMethod "getDisplay" o = SurfaceGetDisplayMethodInfo
    ResolveSurfaceMethod "getFrameClock" o = SurfaceGetFrameClockMethodInfo
    ResolveSurfaceMethod "getHeight" o = SurfaceGetHeightMethodInfo
    ResolveSurfaceMethod "getMapped" o = SurfaceGetMappedMethodInfo
    ResolveSurfaceMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSurfaceMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSurfaceMethod "getScaleFactor" o = SurfaceGetScaleFactorMethodInfo
    ResolveSurfaceMethod "getWidth" o = SurfaceGetWidthMethodInfo
    ResolveSurfaceMethod "setCursor" o = SurfaceSetCursorMethodInfo
    ResolveSurfaceMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSurfaceMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSurfaceMethod "setDeviceCursor" o = SurfaceSetDeviceCursorMethodInfo
    ResolveSurfaceMethod "setInputRegion" o = SurfaceSetInputRegionMethodInfo
    ResolveSurfaceMethod "setOpaqueRegion" o = SurfaceSetOpaqueRegionMethodInfo
    ResolveSurfaceMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSurfaceMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveSurfaceMethod t Surface, O.OverloadedMethod info Surface p) => OL.IsLabel t (Surface -> 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 ~ ResolveSurfaceMethod t Surface, O.OverloadedMethod info Surface p, R.HasField t Surface p) => R.HasField t Surface p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- signal Surface::enter-monitor
-- | Emitted when /@surface@/ starts being present on the monitor.
type SurfaceEnterMonitorCallback =
    Gdk.Monitor.Monitor
    -- ^ /@monitor@/: the monitor
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `SurfaceEnterMonitorCallback`@.
noSurfaceEnterMonitorCallback :: Maybe SurfaceEnterMonitorCallback
noSurfaceEnterMonitorCallback :: Maybe SurfaceEnterMonitorCallback
noSurfaceEnterMonitorCallback = Maybe SurfaceEnterMonitorCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_SurfaceEnterMonitorCallback =
    Ptr () ->                               -- object
    Ptr Gdk.Monitor.Monitor ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_SurfaceEnterMonitor :: MonadIO m => SurfaceEnterMonitorCallback -> m (GClosure C_SurfaceEnterMonitorCallback)
genClosure_SurfaceEnterMonitor :: forall (m :: * -> *).
MonadIO m =>
SurfaceEnterMonitorCallback
-> m (GClosure C_SurfaceEnterMonitorCallback)
genClosure_SurfaceEnterMonitor SurfaceEnterMonitorCallback
cb = IO (GClosure C_SurfaceEnterMonitorCallback)
-> m (GClosure C_SurfaceEnterMonitorCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SurfaceEnterMonitorCallback)
 -> m (GClosure C_SurfaceEnterMonitorCallback))
-> IO (GClosure C_SurfaceEnterMonitorCallback)
-> m (GClosure C_SurfaceEnterMonitorCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEnterMonitorCallback
cb' = SurfaceEnterMonitorCallback -> C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback SurfaceEnterMonitorCallback
cb
    C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceEnterMonitorCallback C_SurfaceEnterMonitorCallback
cb' IO (FunPtr C_SurfaceEnterMonitorCallback)
-> (FunPtr C_SurfaceEnterMonitorCallback
    -> IO (GClosure C_SurfaceEnterMonitorCallback))
-> IO (GClosure C_SurfaceEnterMonitorCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SurfaceEnterMonitorCallback
-> IO (GClosure C_SurfaceEnterMonitorCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SurfaceEnterMonitorCallback` into a `C_SurfaceEnterMonitorCallback`.
wrap_SurfaceEnterMonitorCallback ::
    SurfaceEnterMonitorCallback ->
    C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback :: SurfaceEnterMonitorCallback -> C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback SurfaceEnterMonitorCallback
_cb Ptr ()
_ Ptr Monitor
monitor Ptr ()
_ = do
    Monitor
monitor' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
monitor
    SurfaceEnterMonitorCallback
_cb  Monitor
monitor'


-- | Connect a signal handler for the [enterMonitor](#signal:enterMonitor) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' surface #enterMonitor callback
-- @
-- 
-- 
onSurfaceEnterMonitor :: (IsSurface a, MonadIO m) => a -> SurfaceEnterMonitorCallback -> m SignalHandlerId
onSurfaceEnterMonitor :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceEnterMonitorCallback -> m SignalHandlerId
onSurfaceEnterMonitor a
obj SurfaceEnterMonitorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEnterMonitorCallback
cb' = SurfaceEnterMonitorCallback -> C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback SurfaceEnterMonitorCallback
cb
    FunPtr C_SurfaceEnterMonitorCallback
cb'' <- C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceEnterMonitorCallback C_SurfaceEnterMonitorCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceEnterMonitorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"enter-monitor" FunPtr C_SurfaceEnterMonitorCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [enterMonitor](#signal:enterMonitor) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' surface #enterMonitor callback
-- @
-- 
-- 
afterSurfaceEnterMonitor :: (IsSurface a, MonadIO m) => a -> SurfaceEnterMonitorCallback -> m SignalHandlerId
afterSurfaceEnterMonitor :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceEnterMonitorCallback -> m SignalHandlerId
afterSurfaceEnterMonitor a
obj SurfaceEnterMonitorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEnterMonitorCallback
cb' = SurfaceEnterMonitorCallback -> C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback SurfaceEnterMonitorCallback
cb
    FunPtr C_SurfaceEnterMonitorCallback
cb'' <- C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceEnterMonitorCallback C_SurfaceEnterMonitorCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceEnterMonitorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"enter-monitor" FunPtr C_SurfaceEnterMonitorCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SurfaceEnterMonitorSignalInfo
instance SignalInfo SurfaceEnterMonitorSignalInfo where
    type HaskellCallbackType SurfaceEnterMonitorSignalInfo = SurfaceEnterMonitorCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SurfaceEnterMonitorCallback cb
        cb'' <- mk_SurfaceEnterMonitorCallback cb'
        connectSignalFunPtr obj "enter-monitor" cb'' connectMode detail

#endif

-- signal Surface::event
-- | Emitted when GDK receives an input event for /@surface@/.
type SurfaceEventCallback =
    Gdk.Event.Event
    -- ^ /@event@/: an input event
    -> IO Bool
    -- ^ __Returns:__ 'P.True' to indicate that the event has been handled

-- | A convenience synonym for @`Nothing` :: `Maybe` `SurfaceEventCallback`@.
noSurfaceEventCallback :: Maybe SurfaceEventCallback
noSurfaceEventCallback :: Maybe SurfaceEventCallback
noSurfaceEventCallback = Maybe SurfaceEventCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_SurfaceEventCallback =
    Ptr () ->                               -- object
    Ptr Gdk.Event.Event ->
    Ptr () ->                               -- user_data
    IO CInt

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

-- | Wrap the callback into a `GClosure`.
genClosure_SurfaceEvent :: MonadIO m => SurfaceEventCallback -> m (GClosure C_SurfaceEventCallback)
genClosure_SurfaceEvent :: forall (m :: * -> *).
MonadIO m =>
SurfaceEventCallback -> m (GClosure C_SurfaceEventCallback)
genClosure_SurfaceEvent SurfaceEventCallback
cb = IO (GClosure C_SurfaceEventCallback)
-> m (GClosure C_SurfaceEventCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SurfaceEventCallback)
 -> m (GClosure C_SurfaceEventCallback))
-> IO (GClosure C_SurfaceEventCallback)
-> m (GClosure C_SurfaceEventCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEventCallback
cb' = SurfaceEventCallback -> C_SurfaceEventCallback
wrap_SurfaceEventCallback SurfaceEventCallback
cb
    C_SurfaceEventCallback -> IO (FunPtr C_SurfaceEventCallback)
mk_SurfaceEventCallback C_SurfaceEventCallback
cb' IO (FunPtr C_SurfaceEventCallback)
-> (FunPtr C_SurfaceEventCallback
    -> IO (GClosure C_SurfaceEventCallback))
-> IO (GClosure C_SurfaceEventCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SurfaceEventCallback
-> IO (GClosure C_SurfaceEventCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SurfaceEventCallback` into a `C_SurfaceEventCallback`.
wrap_SurfaceEventCallback ::
    SurfaceEventCallback ->
    C_SurfaceEventCallback
wrap_SurfaceEventCallback :: SurfaceEventCallback -> C_SurfaceEventCallback
wrap_SurfaceEventCallback SurfaceEventCallback
_cb Ptr ()
_ Ptr Event
event Ptr ()
_ = do
    Event
event' <- ((ManagedPtr Event -> Event) -> Ptr Event -> IO Event
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Event -> Event
Gdk.Event.Event) Ptr Event
event
    Bool
result <- SurfaceEventCallback
_cb  Event
event'
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [event](#signal:event) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' surface #event callback
-- @
-- 
-- 
onSurfaceEvent :: (IsSurface a, MonadIO m) => a -> SurfaceEventCallback -> m SignalHandlerId
onSurfaceEvent :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceEventCallback -> m SignalHandlerId
onSurfaceEvent a
obj SurfaceEventCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEventCallback
cb' = SurfaceEventCallback -> C_SurfaceEventCallback
wrap_SurfaceEventCallback SurfaceEventCallback
cb
    FunPtr C_SurfaceEventCallback
cb'' <- C_SurfaceEventCallback -> IO (FunPtr C_SurfaceEventCallback)
mk_SurfaceEventCallback C_SurfaceEventCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceEventCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"event" FunPtr C_SurfaceEventCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [event](#signal:event) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' surface #event callback
-- @
-- 
-- 
afterSurfaceEvent :: (IsSurface a, MonadIO m) => a -> SurfaceEventCallback -> m SignalHandlerId
afterSurfaceEvent :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceEventCallback -> m SignalHandlerId
afterSurfaceEvent a
obj SurfaceEventCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEventCallback
cb' = SurfaceEventCallback -> C_SurfaceEventCallback
wrap_SurfaceEventCallback SurfaceEventCallback
cb
    FunPtr C_SurfaceEventCallback
cb'' <- C_SurfaceEventCallback -> IO (FunPtr C_SurfaceEventCallback)
mk_SurfaceEventCallback C_SurfaceEventCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceEventCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"event" FunPtr C_SurfaceEventCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SurfaceEventSignalInfo
instance SignalInfo SurfaceEventSignalInfo where
    type HaskellCallbackType SurfaceEventSignalInfo = SurfaceEventCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SurfaceEventCallback cb
        cb'' <- mk_SurfaceEventCallback cb'
        connectSignalFunPtr obj "event" cb'' connectMode detail

#endif

-- signal Surface::layout
-- | Emitted when the size of /@surface@/ is changed, or when relayout should
-- be performed.
-- 
-- Surface size is reported in ”application pixels”, not
-- ”device pixels” (see 'GI.Gdk.Objects.Surface.surfaceGetScaleFactor').
type SurfaceLayoutCallback =
    Int32
    -- ^ /@width@/: the current width
    -> Int32
    -- ^ /@height@/: the current height
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `SurfaceLayoutCallback`@.
noSurfaceLayoutCallback :: Maybe SurfaceLayoutCallback
noSurfaceLayoutCallback :: Maybe SurfaceLayoutCallback
noSurfaceLayoutCallback = Maybe SurfaceLayoutCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_SurfaceLayoutCallback =
    Ptr () ->                               -- object
    Int32 ->
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_SurfaceLayout :: MonadIO m => SurfaceLayoutCallback -> m (GClosure C_SurfaceLayoutCallback)
genClosure_SurfaceLayout :: forall (m :: * -> *).
MonadIO m =>
SurfaceLayoutCallback -> m (GClosure C_SurfaceLayoutCallback)
genClosure_SurfaceLayout SurfaceLayoutCallback
cb = IO (GClosure C_SurfaceLayoutCallback)
-> m (GClosure C_SurfaceLayoutCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SurfaceLayoutCallback)
 -> m (GClosure C_SurfaceLayoutCallback))
-> IO (GClosure C_SurfaceLayoutCallback)
-> m (GClosure C_SurfaceLayoutCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceLayoutCallback
cb' = SurfaceLayoutCallback -> C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback SurfaceLayoutCallback
cb
    C_SurfaceLayoutCallback -> IO (FunPtr C_SurfaceLayoutCallback)
mk_SurfaceLayoutCallback C_SurfaceLayoutCallback
cb' IO (FunPtr C_SurfaceLayoutCallback)
-> (FunPtr C_SurfaceLayoutCallback
    -> IO (GClosure C_SurfaceLayoutCallback))
-> IO (GClosure C_SurfaceLayoutCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SurfaceLayoutCallback
-> IO (GClosure C_SurfaceLayoutCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SurfaceLayoutCallback` into a `C_SurfaceLayoutCallback`.
wrap_SurfaceLayoutCallback ::
    SurfaceLayoutCallback ->
    C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback :: SurfaceLayoutCallback -> C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback SurfaceLayoutCallback
_cb Ptr ()
_ Int32
width Int32
height Ptr ()
_ = do
    SurfaceLayoutCallback
_cb  Int32
width Int32
height


-- | Connect a signal handler for the [layout](#signal:layout) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' surface #layout callback
-- @
-- 
-- 
onSurfaceLayout :: (IsSurface a, MonadIO m) => a -> SurfaceLayoutCallback -> m SignalHandlerId
onSurfaceLayout :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceLayoutCallback -> m SignalHandlerId
onSurfaceLayout a
obj SurfaceLayoutCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceLayoutCallback
cb' = SurfaceLayoutCallback -> C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback SurfaceLayoutCallback
cb
    FunPtr C_SurfaceLayoutCallback
cb'' <- C_SurfaceLayoutCallback -> IO (FunPtr C_SurfaceLayoutCallback)
mk_SurfaceLayoutCallback C_SurfaceLayoutCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceLayoutCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"layout" FunPtr C_SurfaceLayoutCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [layout](#signal:layout) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' surface #layout callback
-- @
-- 
-- 
afterSurfaceLayout :: (IsSurface a, MonadIO m) => a -> SurfaceLayoutCallback -> m SignalHandlerId
afterSurfaceLayout :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceLayoutCallback -> m SignalHandlerId
afterSurfaceLayout a
obj SurfaceLayoutCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceLayoutCallback
cb' = SurfaceLayoutCallback -> C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback SurfaceLayoutCallback
cb
    FunPtr C_SurfaceLayoutCallback
cb'' <- C_SurfaceLayoutCallback -> IO (FunPtr C_SurfaceLayoutCallback)
mk_SurfaceLayoutCallback C_SurfaceLayoutCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceLayoutCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"layout" FunPtr C_SurfaceLayoutCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SurfaceLayoutSignalInfo
instance SignalInfo SurfaceLayoutSignalInfo where
    type HaskellCallbackType SurfaceLayoutSignalInfo = SurfaceLayoutCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SurfaceLayoutCallback cb
        cb'' <- mk_SurfaceLayoutCallback cb'
        connectSignalFunPtr obj "layout" cb'' connectMode detail

#endif

-- signal Surface::leave-monitor
-- | Emitted when /@surface@/ stops being present on the monitor.
type SurfaceLeaveMonitorCallback =
    Gdk.Monitor.Monitor
    -- ^ /@monitor@/: the monitor
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `SurfaceLeaveMonitorCallback`@.
noSurfaceLeaveMonitorCallback :: Maybe SurfaceLeaveMonitorCallback
noSurfaceLeaveMonitorCallback :: Maybe SurfaceEnterMonitorCallback
noSurfaceLeaveMonitorCallback = Maybe SurfaceEnterMonitorCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_SurfaceLeaveMonitorCallback =
    Ptr () ->                               -- object
    Ptr Gdk.Monitor.Monitor ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_SurfaceLeaveMonitor :: MonadIO m => SurfaceLeaveMonitorCallback -> m (GClosure C_SurfaceLeaveMonitorCallback)
genClosure_SurfaceLeaveMonitor :: forall (m :: * -> *).
MonadIO m =>
SurfaceEnterMonitorCallback
-> m (GClosure C_SurfaceEnterMonitorCallback)
genClosure_SurfaceLeaveMonitor SurfaceEnterMonitorCallback
cb = IO (GClosure C_SurfaceEnterMonitorCallback)
-> m (GClosure C_SurfaceEnterMonitorCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SurfaceEnterMonitorCallback)
 -> m (GClosure C_SurfaceEnterMonitorCallback))
-> IO (GClosure C_SurfaceEnterMonitorCallback)
-> m (GClosure C_SurfaceEnterMonitorCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEnterMonitorCallback
cb' = SurfaceEnterMonitorCallback -> C_SurfaceEnterMonitorCallback
wrap_SurfaceLeaveMonitorCallback SurfaceEnterMonitorCallback
cb
    C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceLeaveMonitorCallback C_SurfaceEnterMonitorCallback
cb' IO (FunPtr C_SurfaceEnterMonitorCallback)
-> (FunPtr C_SurfaceEnterMonitorCallback
    -> IO (GClosure C_SurfaceEnterMonitorCallback))
-> IO (GClosure C_SurfaceEnterMonitorCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SurfaceEnterMonitorCallback
-> IO (GClosure C_SurfaceEnterMonitorCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SurfaceLeaveMonitorCallback` into a `C_SurfaceLeaveMonitorCallback`.
wrap_SurfaceLeaveMonitorCallback ::
    SurfaceLeaveMonitorCallback ->
    C_SurfaceLeaveMonitorCallback
wrap_SurfaceLeaveMonitorCallback :: SurfaceEnterMonitorCallback -> C_SurfaceEnterMonitorCallback
wrap_SurfaceLeaveMonitorCallback SurfaceEnterMonitorCallback
_cb Ptr ()
_ Ptr Monitor
monitor Ptr ()
_ = do
    Monitor
monitor' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
monitor
    SurfaceEnterMonitorCallback
_cb  Monitor
monitor'


-- | Connect a signal handler for the [leaveMonitor](#signal:leaveMonitor) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' surface #leaveMonitor callback
-- @
-- 
-- 
onSurfaceLeaveMonitor :: (IsSurface a, MonadIO m) => a -> SurfaceLeaveMonitorCallback -> m SignalHandlerId
onSurfaceLeaveMonitor :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceEnterMonitorCallback -> m SignalHandlerId
onSurfaceLeaveMonitor a
obj SurfaceEnterMonitorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEnterMonitorCallback
cb' = SurfaceEnterMonitorCallback -> C_SurfaceEnterMonitorCallback
wrap_SurfaceLeaveMonitorCallback SurfaceEnterMonitorCallback
cb
    FunPtr C_SurfaceEnterMonitorCallback
cb'' <- C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceLeaveMonitorCallback C_SurfaceEnterMonitorCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceEnterMonitorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"leave-monitor" FunPtr C_SurfaceEnterMonitorCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [leaveMonitor](#signal:leaveMonitor) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' surface #leaveMonitor callback
-- @
-- 
-- 
afterSurfaceLeaveMonitor :: (IsSurface a, MonadIO m) => a -> SurfaceLeaveMonitorCallback -> m SignalHandlerId
afterSurfaceLeaveMonitor :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceEnterMonitorCallback -> m SignalHandlerId
afterSurfaceLeaveMonitor a
obj SurfaceEnterMonitorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceEnterMonitorCallback
cb' = SurfaceEnterMonitorCallback -> C_SurfaceEnterMonitorCallback
wrap_SurfaceLeaveMonitorCallback SurfaceEnterMonitorCallback
cb
    FunPtr C_SurfaceEnterMonitorCallback
cb'' <- C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceLeaveMonitorCallback C_SurfaceEnterMonitorCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceEnterMonitorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"leave-monitor" FunPtr C_SurfaceEnterMonitorCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SurfaceLeaveMonitorSignalInfo
instance SignalInfo SurfaceLeaveMonitorSignalInfo where
    type HaskellCallbackType SurfaceLeaveMonitorSignalInfo = SurfaceLeaveMonitorCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SurfaceLeaveMonitorCallback cb
        cb'' <- mk_SurfaceLeaveMonitorCallback cb'
        connectSignalFunPtr obj "leave-monitor" cb'' connectMode detail

#endif

-- signal Surface::render
-- | Emitted when part of the surface needs to be redrawn.
type SurfaceRenderCallback =
    Cairo.Region.Region
    -- ^ /@region@/: the region that needs to be redrawn
    -> IO Bool
    -- ^ __Returns:__ 'P.True' to indicate that the signal has been handled

-- | A convenience synonym for @`Nothing` :: `Maybe` `SurfaceRenderCallback`@.
noSurfaceRenderCallback :: Maybe SurfaceRenderCallback
noSurfaceRenderCallback :: Maybe SurfaceRenderCallback
noSurfaceRenderCallback = Maybe SurfaceRenderCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_SurfaceRenderCallback =
    Ptr () ->                               -- object
    Ptr Cairo.Region.Region ->
    Ptr () ->                               -- user_data
    IO CInt

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

-- | Wrap the callback into a `GClosure`.
genClosure_SurfaceRender :: MonadIO m => SurfaceRenderCallback -> m (GClosure C_SurfaceRenderCallback)
genClosure_SurfaceRender :: forall (m :: * -> *).
MonadIO m =>
SurfaceRenderCallback -> m (GClosure C_SurfaceRenderCallback)
genClosure_SurfaceRender SurfaceRenderCallback
cb = IO (GClosure C_SurfaceRenderCallback)
-> m (GClosure C_SurfaceRenderCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SurfaceRenderCallback)
 -> m (GClosure C_SurfaceRenderCallback))
-> IO (GClosure C_SurfaceRenderCallback)
-> m (GClosure C_SurfaceRenderCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceRenderCallback
cb' = SurfaceRenderCallback -> C_SurfaceRenderCallback
wrap_SurfaceRenderCallback SurfaceRenderCallback
cb
    C_SurfaceRenderCallback -> IO (FunPtr C_SurfaceRenderCallback)
mk_SurfaceRenderCallback C_SurfaceRenderCallback
cb' IO (FunPtr C_SurfaceRenderCallback)
-> (FunPtr C_SurfaceRenderCallback
    -> IO (GClosure C_SurfaceRenderCallback))
-> IO (GClosure C_SurfaceRenderCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SurfaceRenderCallback
-> IO (GClosure C_SurfaceRenderCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SurfaceRenderCallback` into a `C_SurfaceRenderCallback`.
wrap_SurfaceRenderCallback ::
    SurfaceRenderCallback ->
    C_SurfaceRenderCallback
wrap_SurfaceRenderCallback :: SurfaceRenderCallback -> C_SurfaceRenderCallback
wrap_SurfaceRenderCallback SurfaceRenderCallback
_cb Ptr ()
_ Ptr Region
region Ptr ()
_ = do
    (ManagedPtr Region -> Region)
-> Ptr Region -> (Region -> IO CInt) -> IO CInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr Region -> Region
Cairo.Region.Region Ptr Region
region ((Region -> IO CInt) -> IO CInt) -> (Region -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Region
region' -> do
        Bool
result <- SurfaceRenderCallback
_cb  Region
region'
        let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
result
        CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [render](#signal:render) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' surface #render callback
-- @
-- 
-- 
onSurfaceRender :: (IsSurface a, MonadIO m) => a -> SurfaceRenderCallback -> m SignalHandlerId
onSurfaceRender :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceRenderCallback -> m SignalHandlerId
onSurfaceRender a
obj SurfaceRenderCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceRenderCallback
cb' = SurfaceRenderCallback -> C_SurfaceRenderCallback
wrap_SurfaceRenderCallback SurfaceRenderCallback
cb
    FunPtr C_SurfaceRenderCallback
cb'' <- C_SurfaceRenderCallback -> IO (FunPtr C_SurfaceRenderCallback)
mk_SurfaceRenderCallback C_SurfaceRenderCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceRenderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"render" FunPtr C_SurfaceRenderCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [render](#signal:render) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' surface #render callback
-- @
-- 
-- 
afterSurfaceRender :: (IsSurface a, MonadIO m) => a -> SurfaceRenderCallback -> m SignalHandlerId
afterSurfaceRender :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> SurfaceRenderCallback -> m SignalHandlerId
afterSurfaceRender a
obj SurfaceRenderCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SurfaceRenderCallback
cb' = SurfaceRenderCallback -> C_SurfaceRenderCallback
wrap_SurfaceRenderCallback SurfaceRenderCallback
cb
    FunPtr C_SurfaceRenderCallback
cb'' <- C_SurfaceRenderCallback -> IO (FunPtr C_SurfaceRenderCallback)
mk_SurfaceRenderCallback C_SurfaceRenderCallback
cb'
    a
-> Text
-> FunPtr C_SurfaceRenderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"render" FunPtr C_SurfaceRenderCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SurfaceRenderSignalInfo
instance SignalInfo SurfaceRenderSignalInfo where
    type HaskellCallbackType SurfaceRenderSignalInfo = SurfaceRenderCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SurfaceRenderCallback cb
        cb'' <- mk_SurfaceRenderCallback cb'
        connectSignalFunPtr obj "render" cb'' connectMode detail

#endif

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

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

-- | Set the value of the “@cursor@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' surface [ #cursor 'Data.GI.Base.Attributes.:=' value ]
-- @
setSurfaceCursor :: (MonadIO m, IsSurface o, Gdk.Cursor.IsCursor a) => o -> a -> m ()
setSurfaceCursor :: forall (m :: * -> *) o a.
(MonadIO m, IsSurface o, IsCursor a) =>
o -> a -> m ()
setSurfaceCursor o
obj a
val = IO () -> m ()
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
"cursor" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@cursor@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSurfaceCursor :: (IsSurface o, MIO.MonadIO m, Gdk.Cursor.IsCursor a) => a -> m (GValueConstruct o)
constructSurfaceCursor :: forall o (m :: * -> *) a.
(IsSurface o, MonadIO m, IsCursor a) =>
a -> m (GValueConstruct o)
constructSurfaceCursor a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"cursor" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@cursor@” 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' #cursor
-- @
clearSurfaceCursor :: (MonadIO m, IsSurface o) => o -> m ()
clearSurfaceCursor :: forall (m :: * -> *) o. (MonadIO m, IsSurface o) => o -> m ()
clearSurfaceCursor o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Cursor -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"cursor" (Maybe Cursor
forall a. Maybe a
Nothing :: Maybe Gdk.Cursor.Cursor)

#if defined(ENABLE_OVERLOADING)
data SurfaceCursorPropertyInfo
instance AttrInfo SurfaceCursorPropertyInfo where
    type AttrAllowedOps SurfaceCursorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SurfaceCursorPropertyInfo = IsSurface
    type AttrSetTypeConstraint SurfaceCursorPropertyInfo = Gdk.Cursor.IsCursor
    type AttrTransferTypeConstraint SurfaceCursorPropertyInfo = Gdk.Cursor.IsCursor
    type AttrTransferType SurfaceCursorPropertyInfo = Gdk.Cursor.Cursor
    type AttrGetType SurfaceCursorPropertyInfo = (Maybe Gdk.Cursor.Cursor)
    type AttrLabel SurfaceCursorPropertyInfo = "cursor"
    type AttrOrigin SurfaceCursorPropertyInfo = Surface
    attrGet = getSurfaceCursor
    attrSet = setSurfaceCursor
    attrTransfer _ v = do
        unsafeCastTo Gdk.Cursor.Cursor v
    attrConstruct = constructSurfaceCursor
    attrClear = clearSurfaceCursor
#endif

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

-- | 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' surface #display
-- @
getSurfaceDisplay :: (MonadIO m, IsSurface o) => o -> m Gdk.Display.Display
getSurfaceDisplay :: forall (m :: * -> *) o. (MonadIO m, IsSurface o) => o -> m Display
getSurfaceDisplay o
obj = IO Display -> m Display
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
"getSurfaceDisplay" (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

-- | 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`.
constructSurfaceDisplay :: (IsSurface o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructSurfaceDisplay :: forall o (m :: * -> *) a.
(IsSurface o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructSurfaceDisplay a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 SurfaceDisplayPropertyInfo
instance AttrInfo SurfaceDisplayPropertyInfo where
    type AttrAllowedOps SurfaceDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SurfaceDisplayPropertyInfo = IsSurface
    type AttrSetTypeConstraint SurfaceDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint SurfaceDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType SurfaceDisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType SurfaceDisplayPropertyInfo = Gdk.Display.Display
    type AttrLabel SurfaceDisplayPropertyInfo = "display"
    type AttrOrigin SurfaceDisplayPropertyInfo = Surface
    attrGet = getSurfaceDisplay
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructSurfaceDisplay
    attrClear = undefined
#endif

-- VVV Prop "frame-clock"
   -- Type: TInterface (Name {namespace = "Gdk", name = "FrameClock"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@frame-clock@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSurfaceFrameClock :: (IsSurface o, MIO.MonadIO m, Gdk.FrameClock.IsFrameClock a) => a -> m (GValueConstruct o)
constructSurfaceFrameClock :: forall o (m :: * -> *) a.
(IsSurface o, MonadIO m, IsFrameClock a) =>
a -> m (GValueConstruct o)
constructSurfaceFrameClock a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"frame-clock" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data SurfaceFrameClockPropertyInfo
instance AttrInfo SurfaceFrameClockPropertyInfo where
    type AttrAllowedOps SurfaceFrameClockPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SurfaceFrameClockPropertyInfo = IsSurface
    type AttrSetTypeConstraint SurfaceFrameClockPropertyInfo = Gdk.FrameClock.IsFrameClock
    type AttrTransferTypeConstraint SurfaceFrameClockPropertyInfo = Gdk.FrameClock.IsFrameClock
    type AttrTransferType SurfaceFrameClockPropertyInfo = Gdk.FrameClock.FrameClock
    type AttrGetType SurfaceFrameClockPropertyInfo = Gdk.FrameClock.FrameClock
    type AttrLabel SurfaceFrameClockPropertyInfo = "frame-clock"
    type AttrOrigin SurfaceFrameClockPropertyInfo = Surface
    attrGet = getSurfaceFrameClock
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.FrameClock.FrameClock v
    attrConstruct = constructSurfaceFrameClock
    attrClear = undefined
#endif

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

-- | 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' surface #height
-- @
getSurfaceHeight :: (MonadIO m, IsSurface o) => o -> m Int32
getSurfaceHeight :: forall (m :: * -> *) o. (MonadIO m, IsSurface o) => o -> m Int32
getSurfaceHeight o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"height"

#if defined(ENABLE_OVERLOADING)
data SurfaceHeightPropertyInfo
instance AttrInfo SurfaceHeightPropertyInfo where
    type AttrAllowedOps SurfaceHeightPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint SurfaceHeightPropertyInfo = IsSurface
    type AttrSetTypeConstraint SurfaceHeightPropertyInfo = (~) ()
    type AttrTransferTypeConstraint SurfaceHeightPropertyInfo = (~) ()
    type AttrTransferType SurfaceHeightPropertyInfo = ()
    type AttrGetType SurfaceHeightPropertyInfo = Int32
    type AttrLabel SurfaceHeightPropertyInfo = "height"
    type AttrOrigin SurfaceHeightPropertyInfo = Surface
    attrGet = getSurfaceHeight
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@mapped@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' surface #mapped
-- @
getSurfaceMapped :: (MonadIO m, IsSurface o) => o -> m Bool
getSurfaceMapped :: forall (m :: * -> *) o. (MonadIO m, IsSurface o) => o -> m Bool
getSurfaceMapped o
obj = IO Bool -> m Bool
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
"mapped"

#if defined(ENABLE_OVERLOADING)
data SurfaceMappedPropertyInfo
instance AttrInfo SurfaceMappedPropertyInfo where
    type AttrAllowedOps SurfaceMappedPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint SurfaceMappedPropertyInfo = IsSurface
    type AttrSetTypeConstraint SurfaceMappedPropertyInfo = (~) ()
    type AttrTransferTypeConstraint SurfaceMappedPropertyInfo = (~) ()
    type AttrTransferType SurfaceMappedPropertyInfo = ()
    type AttrGetType SurfaceMappedPropertyInfo = Bool
    type AttrLabel SurfaceMappedPropertyInfo = "mapped"
    type AttrOrigin SurfaceMappedPropertyInfo = Surface
    attrGet = getSurfaceMapped
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "scale-factor"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data SurfaceScaleFactorPropertyInfo
instance AttrInfo SurfaceScaleFactorPropertyInfo where
    type AttrAllowedOps SurfaceScaleFactorPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint SurfaceScaleFactorPropertyInfo = IsSurface
    type AttrSetTypeConstraint SurfaceScaleFactorPropertyInfo = (~) ()
    type AttrTransferTypeConstraint SurfaceScaleFactorPropertyInfo = (~) ()
    type AttrTransferType SurfaceScaleFactorPropertyInfo = ()
    type AttrGetType SurfaceScaleFactorPropertyInfo = Int32
    type AttrLabel SurfaceScaleFactorPropertyInfo = "scale-factor"
    type AttrOrigin SurfaceScaleFactorPropertyInfo = Surface
    attrGet = getSurfaceScaleFactor
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | 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' surface #width
-- @
getSurfaceWidth :: (MonadIO m, IsSurface o) => o -> m Int32
getSurfaceWidth :: forall (m :: * -> *) o. (MonadIO m, IsSurface o) => o -> m Int32
getSurfaceWidth o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"width"

#if defined(ENABLE_OVERLOADING)
data SurfaceWidthPropertyInfo
instance AttrInfo SurfaceWidthPropertyInfo where
    type AttrAllowedOps SurfaceWidthPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint SurfaceWidthPropertyInfo = IsSurface
    type AttrSetTypeConstraint SurfaceWidthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint SurfaceWidthPropertyInfo = (~) ()
    type AttrTransferType SurfaceWidthPropertyInfo = ()
    type AttrGetType SurfaceWidthPropertyInfo = Int32
    type AttrLabel SurfaceWidthPropertyInfo = "width"
    type AttrOrigin SurfaceWidthPropertyInfo = Surface
    attrGet = getSurfaceWidth
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Surface
type instance O.AttributeList Surface = SurfaceAttributeList
type SurfaceAttributeList = ('[ '("cursor", SurfaceCursorPropertyInfo), '("display", SurfaceDisplayPropertyInfo), '("frameClock", SurfaceFrameClockPropertyInfo), '("height", SurfaceHeightPropertyInfo), '("mapped", SurfaceMappedPropertyInfo), '("scaleFactor", SurfaceScaleFactorPropertyInfo), '("width", SurfaceWidthPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
surfaceCursor :: AttrLabelProxy "cursor"
surfaceCursor = AttrLabelProxy

surfaceDisplay :: AttrLabelProxy "display"
surfaceDisplay = AttrLabelProxy

surfaceFrameClock :: AttrLabelProxy "frameClock"
surfaceFrameClock = AttrLabelProxy

surfaceHeight :: AttrLabelProxy "height"
surfaceHeight = AttrLabelProxy

surfaceMapped :: AttrLabelProxy "mapped"
surfaceMapped = AttrLabelProxy

surfaceScaleFactor :: AttrLabelProxy "scaleFactor"
surfaceScaleFactor = AttrLabelProxy

surfaceWidth :: AttrLabelProxy "width"
surfaceWidth = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Surface = SurfaceSignalList
type SurfaceSignalList = ('[ '("enterMonitor", SurfaceEnterMonitorSignalInfo), '("event", SurfaceEventSignalInfo), '("layout", SurfaceLayoutSignalInfo), '("leaveMonitor", SurfaceLeaveMonitorSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("render", SurfaceRenderSignalInfo)] :: [(Symbol, *)])

#endif

-- method Surface::new_popup
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent surface to attach the surface to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "autohide"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to hide the surface on outside clicks"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Surface" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_new_popup" gdk_surface_new_popup :: 
    Ptr Surface ->                          -- parent : TInterface (Name {namespace = "Gdk", name = "Surface"})
    CInt ->                                 -- autohide : TBasicType TBoolean
    IO (Ptr Surface)

-- | Create a new popup surface.
-- 
-- The surface will be attached to /@parent@/ and can be positioned
-- relative to it using 'GI.Gdk.Interfaces.Popup.popupPresent'.
surfaceNewPopup ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@parent@/: the parent surface to attach the surface to
    -> Bool
    -- ^ /@autohide@/: whether to hide the surface on outside clicks
    -> m Surface
    -- ^ __Returns:__ a new t'GI.Gdk.Objects.Surface.Surface'
surfaceNewPopup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> Bool -> m Surface
surfaceNewPopup a
parent Bool
autohide = IO Surface -> m Surface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Surface -> m Surface) -> IO Surface -> m Surface
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
parent' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
parent
    let autohide' :: CInt
autohide' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
autohide
    Ptr Surface
result <- Ptr Surface -> CInt -> IO (Ptr Surface)
gdk_surface_new_popup Ptr Surface
parent' CInt
autohide'
    Text -> Ptr Surface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"surfaceNewPopup" Ptr Surface
result
    Surface
result' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Surface -> Surface
Surface) Ptr Surface
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
parent
    Surface -> IO Surface
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Surface::new_toplevel
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the display to create the surface on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Surface" })
-- throws : False
-- Skip return : False

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

-- | Creates a new toplevel surface.
surfaceNewToplevel ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
    a
    -- ^ /@display@/: the display to create the surface on
    -> m Surface
    -- ^ __Returns:__ the new t'GI.Gdk.Objects.Surface.Surface'
surfaceNewToplevel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Surface
surfaceNewToplevel a
display = IO Surface -> m Surface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Surface -> m Surface) -> IO Surface -> m Surface
forall a b. (a -> b) -> a -> b
$ do
    Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
    Ptr Surface
result <- Ptr Display -> IO (Ptr Surface)
gdk_surface_new_toplevel Ptr Display
display'
    Text -> Ptr Surface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"surfaceNewToplevel" Ptr Surface
result
    Surface
result' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Surface -> Surface
Surface) Ptr Surface
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
    Surface -> IO Surface
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Surface::beep
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a toplevel #GdkSurface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_beep" gdk_surface_beep :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO ()

-- | Emits a short beep associated to /@surface@/ in the appropriate
-- display, if supported. Otherwise, emits a short beep on
-- the display just as 'GI.Gdk.Objects.Display.displayBeep'.
surfaceBeep ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a toplevel t'GI.Gdk.Objects.Surface.Surface'
    -> m ()
surfaceBeep :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceBeep a
surface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Surface -> IO ()
gdk_surface_beep Ptr Surface
surface'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SurfaceBeepMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceBeepMethodInfo a signature where
    overloadedMethod = surfaceBeep

instance O.OverloadedMethodInfo SurfaceBeepMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceBeep",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceBeep"
        }


#endif

-- method Surface::create_cairo_context
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gdk" , name = "CairoContext" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_create_cairo_context" gdk_surface_create_cairo_context :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO (Ptr Gdk.CairoContext.CairoContext)

-- | Creates a new t'GI.Gdk.Objects.CairoContext.CairoContext' for rendering on /@surface@/.
surfaceCreateCairoContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m Gdk.CairoContext.CairoContext
    -- ^ __Returns:__ the newly created t'GI.Gdk.Objects.CairoContext.CairoContext'
surfaceCreateCairoContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m CairoContext
surfaceCreateCairoContext a
surface = IO CairoContext -> m CairoContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CairoContext -> m CairoContext)
-> IO CairoContext -> m CairoContext
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr CairoContext
result <- Ptr Surface -> IO (Ptr CairoContext)
gdk_surface_create_cairo_context Ptr Surface
surface'
    Text -> Ptr CairoContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"surfaceCreateCairoContext" Ptr CairoContext
result
    CairoContext
result' <- ((ManagedPtr CairoContext -> CairoContext)
-> Ptr CairoContext -> IO CairoContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr CairoContext -> CairoContext
Gdk.CairoContext.CairoContext) Ptr CairoContext
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    CairoContext -> IO CairoContext
forall (m :: * -> *) a. Monad m => a -> m a
return CairoContext
result'

#if defined(ENABLE_OVERLOADING)
data SurfaceCreateCairoContextMethodInfo
instance (signature ~ (m Gdk.CairoContext.CairoContext), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceCreateCairoContextMethodInfo a signature where
    overloadedMethod = surfaceCreateCairoContext

instance O.OverloadedMethodInfo SurfaceCreateCairoContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceCreateCairoContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceCreateCairoContext"
        }


#endif

-- method Surface::create_gl_context
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "GLContext" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_surface_create_gl_context" gdk_surface_create_gl_context :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gdk.GLContext.GLContext)

-- | Creates a new t'GI.Gdk.Objects.GLContext.GLContext' matching the
-- framebuffer format to the visual of the t'GI.Gdk.Objects.Surface.Surface'. The context
-- is disconnected from any particular surface or surface.
-- 
-- If the creation of the t'GI.Gdk.Objects.GLContext.GLContext' failed, /@error@/ will be set.
-- 
-- Before using the returned t'GI.Gdk.Objects.GLContext.GLContext', you will need to
-- call 'GI.Gdk.Objects.GLContext.gLContextMakeCurrent' or 'GI.Gdk.Objects.GLContext.gLContextRealize'.
surfaceCreateGlContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m Gdk.GLContext.GLContext
    -- ^ __Returns:__ the newly created t'GI.Gdk.Objects.GLContext.GLContext', or
    -- 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
surfaceCreateGlContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m GLContext
surfaceCreateGlContext a
surface = IO GLContext -> m GLContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GLContext -> m GLContext) -> IO GLContext -> m GLContext
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    IO GLContext -> IO () -> IO GLContext
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr GLContext
result <- (Ptr (Ptr GError) -> IO (Ptr GLContext)) -> IO (Ptr GLContext)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr GLContext)) -> IO (Ptr GLContext))
-> (Ptr (Ptr GError) -> IO (Ptr GLContext)) -> IO (Ptr GLContext)
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr (Ptr GError) -> IO (Ptr GLContext)
gdk_surface_create_gl_context Ptr Surface
surface'
        Text -> Ptr GLContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"surfaceCreateGlContext" Ptr GLContext
result
        GLContext
result' <- ((ManagedPtr GLContext -> GLContext)
-> Ptr GLContext -> IO GLContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr GLContext -> GLContext
Gdk.GLContext.GLContext) Ptr GLContext
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
        GLContext -> IO GLContext
forall (m :: * -> *) a. Monad m => a -> m a
return GLContext
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data SurfaceCreateGlContextMethodInfo
instance (signature ~ (m Gdk.GLContext.GLContext), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceCreateGlContextMethodInfo a signature where
    overloadedMethod = surfaceCreateGlContext

instance O.OverloadedMethodInfo SurfaceCreateGlContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceCreateGlContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceCreateGlContext"
        }


#endif

-- method Surface::create_similar_surface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "surface to make new surface similar to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "content"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Content" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the content for the new surface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width of the new surface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height of the new surface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "cairo" , name = "Surface" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_create_similar_surface" gdk_surface_create_similar_surface :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    CUInt ->                                -- content : TInterface (Name {namespace = "cairo", name = "Content"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO (Ptr Cairo.Surface.Surface)

-- | Create a new surface that is as compatible as possible with the
-- given /@surface@/. For example the new surface will have the same
-- fallback resolution and font options as /@surface@/. Generally, the new
-- surface will also use the same backend as /@surface@/, unless that is
-- not possible for some reason. The type of the returned surface may
-- be examined with @/cairo_surface_get_type()/@.
-- 
-- Initially the surface contents are all 0 (transparent if contents
-- have transparency, black otherwise.)
surfaceCreateSimilarSurface ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: surface to make new surface similar to
    -> Cairo.Enums.Content
    -- ^ /@content@/: the content for the new surface
    -> Int32
    -- ^ /@width@/: width of the new surface
    -> Int32
    -- ^ /@height@/: height of the new surface
    -> m Cairo.Surface.Surface
    -- ^ __Returns:__ a pointer to the newly allocated surface. The caller
    -- owns the surface and should call @/cairo_surface_destroy()/@ when done
    -- with it.
    -- 
    -- This function always returns a valid pointer, but it will return a
    -- pointer to a “nil” surface if /@other@/ is already in an error state
    -- or any other error occurs.
surfaceCreateSimilarSurface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> Content -> Int32 -> Int32 -> m Surface
surfaceCreateSimilarSurface a
surface Content
content Int32
width Int32
height = IO Surface -> m Surface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Surface -> m Surface) -> IO Surface -> m Surface
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    let content' :: CUInt
content' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Content -> Int) -> Content -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> Int
forall a. Enum a => a -> Int
fromEnum) Content
content
    Ptr Surface
result <- Ptr Surface -> CUInt -> Int32 -> Int32 -> IO (Ptr Surface)
gdk_surface_create_similar_surface Ptr Surface
surface' CUInt
content' Int32
width Int32
height
    Text -> Ptr Surface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"surfaceCreateSimilarSurface" Ptr Surface
result
    Surface
result' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Surface -> Surface
Cairo.Surface.Surface) Ptr Surface
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Surface -> IO Surface
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result'

#if defined(ENABLE_OVERLOADING)
data SurfaceCreateSimilarSurfaceMethodInfo
instance (signature ~ (Cairo.Enums.Content -> Int32 -> Int32 -> m Cairo.Surface.Surface), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceCreateSimilarSurfaceMethodInfo a signature where
    overloadedMethod = surfaceCreateSimilarSurface

instance O.OverloadedMethodInfo SurfaceCreateSimilarSurfaceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceCreateSimilarSurface",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceCreateSimilarSurface"
        }


#endif

-- method Surface::create_vulkan_context
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gdk" , name = "VulkanContext" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_surface_create_vulkan_context" gdk_surface_create_vulkan_context :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gdk.VulkanContext.VulkanContext)

-- | Creates a new t'GI.Gdk.Objects.VulkanContext.VulkanContext' for rendering on /@surface@/.
-- 
-- If the creation of the t'GI.Gdk.Objects.VulkanContext.VulkanContext' failed, /@error@/ will be set.
surfaceCreateVulkanContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m Gdk.VulkanContext.VulkanContext
    -- ^ __Returns:__ the newly created t'GI.Gdk.Objects.VulkanContext.VulkanContext', or
    -- 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
surfaceCreateVulkanContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m VulkanContext
surfaceCreateVulkanContext a
surface = IO VulkanContext -> m VulkanContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VulkanContext -> m VulkanContext)
-> IO VulkanContext -> m VulkanContext
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    IO VulkanContext -> IO () -> IO VulkanContext
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr VulkanContext
result <- (Ptr (Ptr GError) -> IO (Ptr VulkanContext))
-> IO (Ptr VulkanContext)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr VulkanContext))
 -> IO (Ptr VulkanContext))
-> (Ptr (Ptr GError) -> IO (Ptr VulkanContext))
-> IO (Ptr VulkanContext)
forall a b. (a -> b) -> a -> b
$ Ptr Surface -> Ptr (Ptr GError) -> IO (Ptr VulkanContext)
gdk_surface_create_vulkan_context Ptr Surface
surface'
        Text -> Ptr VulkanContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"surfaceCreateVulkanContext" Ptr VulkanContext
result
        VulkanContext
result' <- ((ManagedPtr VulkanContext -> VulkanContext)
-> Ptr VulkanContext -> IO VulkanContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr VulkanContext -> VulkanContext
Gdk.VulkanContext.VulkanContext) Ptr VulkanContext
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
        VulkanContext -> IO VulkanContext
forall (m :: * -> *) a. Monad m => a -> m a
return VulkanContext
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data SurfaceCreateVulkanContextMethodInfo
instance (signature ~ (m Gdk.VulkanContext.VulkanContext), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceCreateVulkanContextMethodInfo a signature where
    overloadedMethod = surfaceCreateVulkanContext

instance O.OverloadedMethodInfo SurfaceCreateVulkanContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceCreateVulkanContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceCreateVulkanContext"
        }


#endif

-- method Surface::destroy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_destroy" gdk_surface_destroy :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO ()

-- | Destroys the window system resources associated with /@surface@/ and decrements /@surface@/\'s
-- reference count. The window system resources for all children of /@surface@/ are also
-- destroyed, but the children’s reference counts are not decremented.
-- 
-- Note that a surface will not be destroyed automatically when its reference count
-- reaches zero. You must call this function yourself before that happens.
surfaceDestroy ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m ()
surfaceDestroy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceDestroy a
surface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Surface -> IO ()
gdk_surface_destroy Ptr Surface
surface'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SurfaceDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceDestroyMethodInfo a signature where
    overloadedMethod = surfaceDestroy

instance O.OverloadedMethodInfo SurfaceDestroyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceDestroy",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceDestroy"
        }


#endif

-- method Surface::get_cursor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Cursor" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_get_cursor" gdk_surface_get_cursor :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO (Ptr Gdk.Cursor.Cursor)

-- | Retrieves a t'GI.Gdk.Objects.Cursor.Cursor' pointer for the cursor currently set on the
-- specified t'GI.Gdk.Objects.Surface.Surface', or 'P.Nothing'.  If the return value is 'P.Nothing' then
-- there is no custom cursor set on the specified surface, and it is
-- using the cursor for its parent surface.
surfaceGetCursor ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m (Maybe Gdk.Cursor.Cursor)
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Cursor.Cursor', or 'P.Nothing'. The
    --   returned object is owned by the t'GI.Gdk.Objects.Surface.Surface' and should not be
    --   unreferenced directly. Use 'GI.Gdk.Objects.Surface.surfaceSetCursor' to unset the
    --   cursor of the surface
surfaceGetCursor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m (Maybe Cursor)
surfaceGetCursor a
surface = IO (Maybe Cursor) -> m (Maybe Cursor)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Cursor) -> m (Maybe Cursor))
-> IO (Maybe Cursor) -> m (Maybe Cursor)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Cursor
result <- Ptr Surface -> IO (Ptr Cursor)
gdk_surface_get_cursor Ptr Surface
surface'
    Maybe Cursor
maybeResult <- Ptr Cursor -> (Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Cursor
result ((Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor))
-> (Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor)
forall a b. (a -> b) -> a -> b
$ \Ptr Cursor
result' -> do
        Cursor
result'' <- ((ManagedPtr Cursor -> Cursor) -> Ptr Cursor -> IO Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Cursor -> Cursor
Gdk.Cursor.Cursor) Ptr Cursor
result'
        Cursor -> IO Cursor
forall (m :: * -> *) a. Monad m => a -> m a
return Cursor
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Maybe Cursor -> IO (Maybe Cursor)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Cursor
maybeResult

#if defined(ENABLE_OVERLOADING)
data SurfaceGetCursorMethodInfo
instance (signature ~ (m (Maybe Gdk.Cursor.Cursor)), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceGetCursorMethodInfo a signature where
    overloadedMethod = surfaceGetCursor

instance O.OverloadedMethodInfo SurfaceGetCursorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetCursor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetCursor"
        }


#endif

-- method Surface::get_device_cursor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a logical, pointer #GdkDevice."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Cursor" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_get_device_cursor" gdk_surface_get_device_cursor :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    Ptr Gdk.Device.Device ->                -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO (Ptr Gdk.Cursor.Cursor)

-- | Retrieves a t'GI.Gdk.Objects.Cursor.Cursor' pointer for the /@device@/ currently set on the
-- specified t'GI.Gdk.Objects.Surface.Surface', or 'P.Nothing'.  If the return value is 'P.Nothing' then
-- there is no custom cursor set on the specified surface, and it is
-- using the cursor for its parent surface.
surfaceGetDeviceCursor ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a, Gdk.Device.IsDevice b) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'.
    -> b
    -- ^ /@device@/: a logical, pointer t'GI.Gdk.Objects.Device.Device'.
    -> m (Maybe Gdk.Cursor.Cursor)
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Cursor.Cursor', or 'P.Nothing'. The
    --   returned object is owned by the t'GI.Gdk.Objects.Surface.Surface' and should not be
    --   unreferenced directly. Use 'GI.Gdk.Objects.Surface.surfaceSetCursor' to unset the
    --   cursor of the surface
surfaceGetDeviceCursor :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSurface a, IsDevice b) =>
a -> b -> m (Maybe Cursor)
surfaceGetDeviceCursor a
surface b
device = IO (Maybe Cursor) -> m (Maybe Cursor)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Cursor) -> m (Maybe Cursor))
-> IO (Maybe Cursor) -> m (Maybe Cursor)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Device
device' <- b -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
device
    Ptr Cursor
result <- Ptr Surface -> Ptr Device -> IO (Ptr Cursor)
gdk_surface_get_device_cursor Ptr Surface
surface' Ptr Device
device'
    Maybe Cursor
maybeResult <- Ptr Cursor -> (Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Cursor
result ((Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor))
-> (Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor)
forall a b. (a -> b) -> a -> b
$ \Ptr Cursor
result' -> do
        Cursor
result'' <- ((ManagedPtr Cursor -> Cursor) -> Ptr Cursor -> IO Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Cursor -> Cursor
Gdk.Cursor.Cursor) Ptr Cursor
result'
        Cursor -> IO Cursor
forall (m :: * -> *) a. Monad m => a -> m a
return Cursor
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
device
    Maybe Cursor -> IO (Maybe Cursor)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Cursor
maybeResult

#if defined(ENABLE_OVERLOADING)
data SurfaceGetDeviceCursorMethodInfo
instance (signature ~ (b -> m (Maybe Gdk.Cursor.Cursor)), MonadIO m, IsSurface a, Gdk.Device.IsDevice b) => O.OverloadedMethod SurfaceGetDeviceCursorMethodInfo a signature where
    overloadedMethod = surfaceGetDeviceCursor

instance O.OverloadedMethodInfo SurfaceGetDeviceCursorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetDeviceCursor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetDeviceCursor"
        }


#endif

-- method Surface::get_device_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer #GdkDevice to query to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the X coordinate of @device, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the Y coordinate of @device, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "mask"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the modifier mask, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_get_device_position" gdk_surface_get_device_position :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    Ptr Gdk.Device.Device ->                -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr CDouble ->                          -- x : TBasicType TDouble
    Ptr CDouble ->                          -- y : TBasicType TDouble
    Ptr CUInt ->                            -- mask : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    IO CInt

-- | Obtains the current device position in doubles and modifier state.
-- The position is given in coordinates relative to the upper left
-- corner of /@surface@/.
surfaceGetDevicePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a, Gdk.Device.IsDevice b) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'.
    -> b
    -- ^ /@device@/: pointer t'GI.Gdk.Objects.Device.Device' to query to.
    -> m ((Bool, Double, Double, [Gdk.Flags.ModifierType]))
    -- ^ __Returns:__ 'P.True' if the device is over the surface
surfaceGetDevicePosition :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSurface a, IsDevice b) =>
a -> b -> m (Bool, Double, Double, [ModifierType])
surfaceGetDevicePosition a
surface b
device = IO (Bool, Double, Double, [ModifierType])
-> m (Bool, Double, Double, [ModifierType])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Double, Double, [ModifierType])
 -> m (Bool, Double, Double, [ModifierType]))
-> IO (Bool, Double, Double, [ModifierType])
-> m (Bool, Double, Double, [ModifierType])
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Device
device' <- b -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
device
    Ptr CDouble
x <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
y <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CUInt
mask <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    CInt
result <- Ptr Surface
-> Ptr Device -> Ptr CDouble -> Ptr CDouble -> Ptr CUInt -> IO CInt
gdk_surface_get_device_position Ptr Surface
surface' Ptr Device
device' Ptr CDouble
x Ptr CDouble
y Ptr CUInt
mask
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    CDouble
x' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
x
    let x'' :: Double
x'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x'
    CDouble
y' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
y
    let y'' :: Double
y'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y'
    CUInt
mask' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
mask
    let mask'' :: [ModifierType]
mask'' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
mask'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
device
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
x
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
y
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
mask
    (Bool, Double, Double, [ModifierType])
-> IO (Bool, Double, Double, [ModifierType])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Double
x'', Double
y'', [ModifierType]
mask'')

#if defined(ENABLE_OVERLOADING)
data SurfaceGetDevicePositionMethodInfo
instance (signature ~ (b -> m ((Bool, Double, Double, [Gdk.Flags.ModifierType]))), MonadIO m, IsSurface a, Gdk.Device.IsDevice b) => O.OverloadedMethod SurfaceGetDevicePositionMethodInfo a signature where
    overloadedMethod = surfaceGetDevicePosition

instance O.OverloadedMethodInfo SurfaceGetDevicePositionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetDevicePosition",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetDevicePosition"
        }


#endif

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

foreign import ccall "gdk_surface_get_display" gdk_surface_get_display :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO (Ptr Gdk.Display.Display)

-- | Gets the t'GI.Gdk.Objects.Display.Display' associated with a t'GI.Gdk.Objects.Surface.Surface'.
surfaceGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m Gdk.Display.Display
    -- ^ __Returns:__ the t'GI.Gdk.Objects.Display.Display' associated with /@surface@/
surfaceGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Display
surfaceGetDisplay a
surface = IO Display -> m Display
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
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Display
result <- Ptr Surface -> IO (Ptr Display)
gdk_surface_get_display Ptr Surface
surface'
    Text -> Ptr Display -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"surfaceGetDisplay" Ptr Display
result
    Display
result' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Display -> IO Display
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result'

#if defined(ENABLE_OVERLOADING)
data SurfaceGetDisplayMethodInfo
instance (signature ~ (m Gdk.Display.Display), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceGetDisplayMethodInfo a signature where
    overloadedMethod = surfaceGetDisplay

instance O.OverloadedMethodInfo SurfaceGetDisplayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetDisplay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetDisplay"
        }


#endif

-- method Surface::get_frame_clock
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "surface to get frame clock for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "FrameClock" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_get_frame_clock" gdk_surface_get_frame_clock :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO (Ptr Gdk.FrameClock.FrameClock)

-- | Gets the frame clock for the surface. The frame clock for a surface
-- never changes unless the surface is reparented to a new toplevel
-- surface.
surfaceGetFrameClock ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: surface to get frame clock for
    -> m Gdk.FrameClock.FrameClock
    -- ^ __Returns:__ the frame clock
surfaceGetFrameClock :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m FrameClock
surfaceGetFrameClock a
surface = IO FrameClock -> m FrameClock
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FrameClock -> m FrameClock) -> IO FrameClock -> m FrameClock
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr FrameClock
result <- Ptr Surface -> IO (Ptr FrameClock)
gdk_surface_get_frame_clock Ptr Surface
surface'
    Text -> Ptr FrameClock -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"surfaceGetFrameClock" Ptr FrameClock
result
    FrameClock
result' <- ((ManagedPtr FrameClock -> FrameClock)
-> Ptr FrameClock -> IO FrameClock
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FrameClock -> FrameClock
Gdk.FrameClock.FrameClock) Ptr FrameClock
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    FrameClock -> IO FrameClock
forall (m :: * -> *) a. Monad m => a -> m a
return FrameClock
result'

#if defined(ENABLE_OVERLOADING)
data SurfaceGetFrameClockMethodInfo
instance (signature ~ (m Gdk.FrameClock.FrameClock), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceGetFrameClockMethodInfo a signature where
    overloadedMethod = surfaceGetFrameClock

instance O.OverloadedMethodInfo SurfaceGetFrameClockMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetFrameClock",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetFrameClock"
        }


#endif

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

foreign import ccall "gdk_surface_get_height" gdk_surface_get_height :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO Int32

-- | Returns the height of the given /@surface@/.
-- 
-- Surface size is reported in ”application pixels”, not
-- ”device pixels” (see 'GI.Gdk.Objects.Surface.surfaceGetScaleFactor').
surfaceGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m Int32
    -- ^ __Returns:__ The height of /@surface@/
surfaceGetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Int32
surfaceGetHeight a
surface = IO Int32 -> m Int32
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
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Int32
result <- Ptr Surface -> IO Int32
gdk_surface_get_height Ptr Surface
surface'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data SurfaceGetHeightMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceGetHeightMethodInfo a signature where
    overloadedMethod = surfaceGetHeight

instance O.OverloadedMethodInfo SurfaceGetHeightMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetHeight",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetHeight"
        }


#endif

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

foreign import ccall "gdk_surface_get_mapped" gdk_surface_get_mapped :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO CInt

-- | Checks whether the surface has been mapped (with 'GI.Gdk.Interfaces.Toplevel.toplevelPresent'
-- or 'GI.Gdk.Interfaces.Popup.popupPresent').
surfaceGetMapped ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the surface is mapped
surfaceGetMapped :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Bool
surfaceGetMapped a
surface = IO Bool -> m Bool
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
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    CInt
result <- Ptr Surface -> IO CInt
gdk_surface_get_mapped Ptr Surface
surface'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SurfaceGetMappedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceGetMappedMethodInfo a signature where
    overloadedMethod = surfaceGetMapped

instance O.OverloadedMethodInfo SurfaceGetMappedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetMapped",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetMapped"
        }


#endif

-- method Surface::get_scale_factor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "surface to get scale factor for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_get_scale_factor" gdk_surface_get_scale_factor :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO Int32

-- | Returns the internal scale factor that maps from surface coordinates
-- to the actual device pixels. On traditional systems this is 1, but
-- on very high density outputs this can be a higher value (often 2).
-- 
-- A higher value means that drawing is automatically scaled up to
-- a higher resolution, so any code doing drawing will automatically look
-- nicer. However, if you are supplying pixel-based data the scale
-- value can be used to determine whether to use a pixel resource
-- with higher resolution data.
-- 
-- The scale of a surface may change during runtime.
surfaceGetScaleFactor ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: surface to get scale factor for
    -> m Int32
    -- ^ __Returns:__ the scale factor
surfaceGetScaleFactor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Int32
surfaceGetScaleFactor a
surface = IO Int32 -> m Int32
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
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Int32
result <- Ptr Surface -> IO Int32
gdk_surface_get_scale_factor Ptr Surface
surface'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data SurfaceGetScaleFactorMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceGetScaleFactorMethodInfo a signature where
    overloadedMethod = surfaceGetScaleFactor

instance O.OverloadedMethodInfo SurfaceGetScaleFactorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetScaleFactor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetScaleFactor"
        }


#endif

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

foreign import ccall "gdk_surface_get_width" gdk_surface_get_width :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO Int32

-- | Returns the width of the given /@surface@/.
-- 
-- Surface size is reported in ”application pixels”, not
-- ”device pixels” (see 'GI.Gdk.Objects.Surface.surfaceGetScaleFactor').
surfaceGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m Int32
    -- ^ __Returns:__ The width of /@surface@/
surfaceGetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Int32
surfaceGetWidth a
surface = IO Int32 -> m Int32
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
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Int32
result <- Ptr Surface -> IO Int32
gdk_surface_get_width Ptr Surface
surface'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data SurfaceGetWidthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceGetWidthMethodInfo a signature where
    overloadedMethod = surfaceGetWidth

instance O.OverloadedMethodInfo SurfaceGetWidthMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceGetWidth",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetWidth"
        }


#endif

-- method Surface::hide
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_hide" gdk_surface_hide :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO ()

-- | For toplevel surfaces, withdraws them, so they will no longer be
-- known to the window manager; for all surfaces, unmaps them, so
-- they won’t be displayed. Normally done automatically as
-- part of @/gtk_widget_hide()/@.
surfaceHide ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m ()
surfaceHide :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceHide a
surface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Surface -> IO ()
gdk_surface_hide Ptr Surface
surface'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SurfaceHideMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceHideMethodInfo a signature where
    overloadedMethod = surfaceHide

instance O.OverloadedMethodInfo SurfaceHideMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceHide",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceHide"
        }


#endif

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

foreign import ccall "gdk_surface_is_destroyed" gdk_surface_is_destroyed :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO CInt

-- | Check to see if a surface is destroyed..
surfaceIsDestroyed ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the surface is destroyed
surfaceIsDestroyed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Bool
surfaceIsDestroyed a
surface = IO Bool -> m Bool
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
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    CInt
result <- Ptr Surface -> IO CInt
gdk_surface_is_destroyed Ptr Surface
surface'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SurfaceIsDestroyedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceIsDestroyedMethodInfo a signature where
    overloadedMethod = surfaceIsDestroyed

instance O.OverloadedMethodInfo SurfaceIsDestroyedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceIsDestroyed",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceIsDestroyed"
        }


#endif

-- method Surface::queue_render
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_queue_render" gdk_surface_queue_render :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO ()

-- | Forces a [render]("GI.Gdk.Objects.Surface#g:signal:render") signal emission for /@surface@/
-- to be scheduled.
-- 
-- This function is useful for implementations that track invalid
-- regions on their own.
surfaceQueueRender ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m ()
surfaceQueueRender :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceQueueRender a
surface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Surface -> IO ()
gdk_surface_queue_render Ptr Surface
surface'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SurfaceQueueRenderMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceQueueRenderMethodInfo a signature where
    overloadedMethod = surfaceQueueRender

instance O.OverloadedMethodInfo SurfaceQueueRenderMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceQueueRender",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceQueueRender"
        }


#endif

-- method Surface::request_layout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_request_layout" gdk_surface_request_layout :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    IO ()

-- | Request a 'GI.Gdk.Flags.FrameClockPhaseLayout' from the surface\'s
-- frame clock. See 'GI.Gdk.Objects.FrameClock.frameClockRequestPhase'.
surfaceRequestLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> m ()
surfaceRequestLayout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceRequestLayout a
surface = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Surface -> IO ()
gdk_surface_request_layout Ptr Surface
surface'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SurfaceRequestLayoutMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceRequestLayoutMethodInfo a signature where
    overloadedMethod = surfaceRequestLayout

instance O.OverloadedMethodInfo SurfaceRequestLayoutMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceRequestLayout",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceRequestLayout"
        }


#endif

-- method Surface::set_cursor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cursor"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Cursor" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a cursor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_set_cursor" gdk_surface_set_cursor :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    Ptr Gdk.Cursor.Cursor ->                -- cursor : TInterface (Name {namespace = "Gdk", name = "Cursor"})
    IO ()

-- | Sets the default mouse pointer for a t'GI.Gdk.Objects.Surface.Surface'.
-- 
-- Note that /@cursor@/ must be for the same display as /@surface@/.
-- 
-- Use 'GI.Gdk.Objects.Cursor.cursorNewFromName' or 'GI.Gdk.Objects.Cursor.cursorNewFromTexture' to
-- create the cursor. To make the cursor invisible, use @/GDK_BLANK_CURSOR/@.
-- Passing 'P.Nothing' for the /@cursor@/ argument to 'GI.Gdk.Objects.Surface.surfaceSetCursor' means
-- that /@surface@/ will use the cursor of its parent surface. Most surfaces
-- should use this default.
surfaceSetCursor ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a, Gdk.Cursor.IsCursor b) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> Maybe (b)
    -- ^ /@cursor@/: a cursor
    -> m ()
surfaceSetCursor :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSurface a, IsCursor b) =>
a -> Maybe b -> m ()
surfaceSetCursor a
surface Maybe b
cursor = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Cursor
maybeCursor <- case Maybe b
cursor of
        Maybe b
Nothing -> Ptr Cursor -> IO (Ptr Cursor)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cursor
forall a. Ptr a
nullPtr
        Just b
jCursor -> do
            Ptr Cursor
jCursor' <- b -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCursor
            Ptr Cursor -> IO (Ptr Cursor)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cursor
jCursor'
    Ptr Surface -> Ptr Cursor -> IO ()
gdk_surface_set_cursor Ptr Surface
surface' Ptr Cursor
maybeCursor
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cursor b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SurfaceSetCursorMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsSurface a, Gdk.Cursor.IsCursor b) => O.OverloadedMethod SurfaceSetCursorMethodInfo a signature where
    overloadedMethod = surfaceSetCursor

instance O.OverloadedMethodInfo SurfaceSetCursorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceSetCursor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceSetCursor"
        }


#endif

-- method Surface::set_device_cursor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a logical, pointer #GdkDevice"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cursor"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Cursor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkCursor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_set_device_cursor" gdk_surface_set_device_cursor :: 
    Ptr Surface ->                          -- surface : TInterface (Name {namespace = "Gdk", name = "Surface"})
    Ptr Gdk.Device.Device ->                -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr Gdk.Cursor.Cursor ->                -- cursor : TInterface (Name {namespace = "Gdk", name = "Cursor"})
    IO ()

-- | Sets a specific t'GI.Gdk.Objects.Cursor.Cursor' for a given device when it gets inside /@surface@/.
-- Use 'GI.Gdk.Objects.Cursor.cursorNewFromName' or 'GI.Gdk.Objects.Cursor.cursorNewFromTexture' to create
-- the cursor. To make the cursor invisible, use @/GDK_BLANK_CURSOR/@. Passing
-- 'P.Nothing' for the /@cursor@/ argument to 'GI.Gdk.Objects.Surface.surfaceSetCursor' means that
-- /@surface@/ will use the cursor of its parent surface. Most surfaces should
-- use this default.
surfaceSetDeviceCursor ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a, Gdk.Device.IsDevice b, Gdk.Cursor.IsCursor c) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> b
    -- ^ /@device@/: a logical, pointer t'GI.Gdk.Objects.Device.Device'
    -> c
    -- ^ /@cursor@/: a t'GI.Gdk.Objects.Cursor.Cursor'
    -> m ()
surfaceSetDeviceCursor :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSurface a, IsDevice b, IsCursor c) =>
a -> b -> c -> m ()
surfaceSetDeviceCursor a
surface b
device c
cursor = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Device
device' <- b -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
device
    Ptr Cursor
cursor' <- c -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
cursor
    Ptr Surface -> Ptr Device -> Ptr Cursor -> IO ()
gdk_surface_set_device_cursor Ptr Surface
surface' Ptr Device
device' Ptr Cursor
cursor'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
device
    c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
cursor
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SurfaceSetDeviceCursorMethodInfo
instance (signature ~ (b -> c -> m ()), MonadIO m, IsSurface a, Gdk.Device.IsDevice b, Gdk.Cursor.IsCursor c) => O.OverloadedMethod SurfaceSetDeviceCursorMethodInfo a signature where
    overloadedMethod = surfaceSetDeviceCursor

instance O.OverloadedMethodInfo SurfaceSetDeviceCursorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceSetDeviceCursor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceSetDeviceCursor"
        }


#endif

-- method Surface::set_input_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkSurface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "region"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Region" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "region of surface to be reactive"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Apply the region to the surface for the purpose of event
-- handling. Mouse events which happen while the pointer position
-- corresponds to an unset bit in the mask will be passed on the
-- surface below /@surface@/.
-- 
-- An input region is typically used with RGBA surfaces.
-- The alpha channel of the surface defines which pixels are
-- invisible and allows for nicely antialiased borders,
-- and the input region controls where the surface is
-- “clickable”.
-- 
-- Use 'GI.Gdk.Objects.Display.displaySupportsInputShapes' to find out if
-- a particular backend supports input regions.
surfaceSetInputRegion ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a t'GI.Gdk.Objects.Surface.Surface'
    -> Cairo.Region.Region
    -- ^ /@region@/: region of surface to be reactive
    -> m ()
surfaceSetInputRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> Region -> m ()
surfaceSetInputRegion a
surface Region
region = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Region
region' <- Region -> IO (Ptr Region)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Region
region
    Ptr Surface -> Ptr Region -> IO ()
gdk_surface_set_input_region Ptr Surface
surface' Ptr Region
region'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Region -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Region
region
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SurfaceSetInputRegionMethodInfo
instance (signature ~ (Cairo.Region.Region -> m ()), MonadIO m, IsSurface a) => O.OverloadedMethod SurfaceSetInputRegionMethodInfo a signature where
    overloadedMethod = surfaceSetInputRegion

instance O.OverloadedMethodInfo SurfaceSetInputRegionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceSetInputRegion",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceSetInputRegion"
        }


#endif

-- method Surface::set_opaque_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a top-level or non-native #GdkSurface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "region"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Region" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a region, or %NULL" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | For optimisation purposes, compositing window managers may
-- like to not draw obscured regions of surfaces, or turn off blending
-- during for these regions. With RGB windows with no transparency,
-- this is just the shape of the window, but with ARGB32 windows, the
-- compositor does not know what regions of the window are transparent
-- or not.
-- 
-- This function only works for toplevel surfaces.
-- 
-- GTK will update this property automatically if
-- the /@surface@/ background is opaque, as we know where the opaque regions
-- are. If your surface background is not opaque, please update this
-- property in your @/GtkWidgetClass.css_changed()/@ handler.
surfaceSetOpaqueRegion ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
    a
    -- ^ /@surface@/: a top-level or non-native t'GI.Gdk.Objects.Surface.Surface'
    -> Maybe (Cairo.Region.Region)
    -- ^ /@region@/: a region, or 'P.Nothing'
    -> m ()
surfaceSetOpaqueRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> Maybe Region -> m ()
surfaceSetOpaqueRegion a
surface Maybe Region
region = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
surface' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
surface
    Ptr Region
maybeRegion <- case Maybe Region
region of
        Maybe Region
Nothing -> Ptr Region -> IO (Ptr Region)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Region
forall a. Ptr a
nullPtr
        Just Region
jRegion -> do
            Ptr Region
jRegion' <- Region -> IO (Ptr Region)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Region
jRegion
            Ptr Region -> IO (Ptr Region)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Region
jRegion'
    Ptr Surface -> Ptr Region -> IO ()
gdk_surface_set_opaque_region Ptr Surface
surface' Ptr Region
maybeRegion
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
surface
    Maybe Region -> (Region -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Region
region Region -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo SurfaceSetOpaqueRegionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceSetOpaqueRegion",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceSetOpaqueRegion"
        }


#endif

-- method Surface::translate_coordinates
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "from"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the origin surface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "to"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the target surface" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "coordinates to translate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "coordinates to translate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_surface_translate_coordinates" gdk_surface_translate_coordinates :: 
    Ptr Surface ->                          -- from : TInterface (Name {namespace = "Gdk", name = "Surface"})
    Ptr Surface ->                          -- to : TInterface (Name {namespace = "Gdk", name = "Surface"})
    CDouble ->                              -- x : TBasicType TDouble
    CDouble ->                              -- y : TBasicType TDouble
    IO CInt

-- | Translates the given coordinates from being
-- relative to the /@from@/ surface to being relative
-- to the /@to@/ surface.
-- 
-- Note that this only works if /@to@/ and /@from@/ are
-- popups or transient-for to the same toplevel
-- (directly or indirectly).
surfaceTranslateCoordinates ::
    (B.CallStack.HasCallStack, MonadIO m, IsSurface a, IsSurface b) =>
    a
    -- ^ /@from@/: the origin surface
    -> b
    -- ^ /@to@/: the target surface
    -> Double
    -- ^ /@x@/: coordinates to translate
    -> Double
    -- ^ /@y@/: coordinates to translate
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the coordinates were successfully
    --     translated
surfaceTranslateCoordinates :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSurface a, IsSurface b) =>
a -> b -> Double -> Double -> m Bool
surfaceTranslateCoordinates a
from b
to Double
x Double
y = IO Bool -> m Bool
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
    Ptr Surface
from' <- a -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
from
    Ptr Surface
to' <- b -> IO (Ptr Surface)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
to
    let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
    let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
    CInt
result <- Ptr Surface -> Ptr Surface -> CDouble -> CDouble -> IO CInt
gdk_surface_translate_coordinates Ptr Surface
from' Ptr Surface
to' CDouble
x' CDouble
y'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
from
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
to
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SurfaceTranslateCoordinatesMethodInfo
instance (signature ~ (b -> Double -> Double -> m Bool), MonadIO m, IsSurface a, IsSurface b) => O.OverloadedMethod SurfaceTranslateCoordinatesMethodInfo a signature where
    overloadedMethod = surfaceTranslateCoordinates

instance O.OverloadedMethodInfo SurfaceTranslateCoordinatesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Surface.surfaceTranslateCoordinates",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-Surface.html#v:surfaceTranslateCoordinates"
        }


#endif