{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.Surface
(
Surface(..) ,
IsSurface ,
toSurface ,
#if defined(ENABLE_OVERLOADING)
ResolveSurfaceMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SurfaceBeepMethodInfo ,
#endif
surfaceBeep ,
#if defined(ENABLE_OVERLOADING)
SurfaceCreateCairoContextMethodInfo ,
#endif
surfaceCreateCairoContext ,
#if defined(ENABLE_OVERLOADING)
SurfaceCreateGlContextMethodInfo ,
#endif
surfaceCreateGlContext ,
#if defined(ENABLE_OVERLOADING)
SurfaceCreateSimilarSurfaceMethodInfo ,
#endif
surfaceCreateSimilarSurface ,
#if defined(ENABLE_OVERLOADING)
SurfaceCreateVulkanContextMethodInfo ,
#endif
surfaceCreateVulkanContext ,
#if defined(ENABLE_OVERLOADING)
SurfaceDestroyMethodInfo ,
#endif
surfaceDestroy ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetCursorMethodInfo ,
#endif
surfaceGetCursor ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetDeviceCursorMethodInfo ,
#endif
surfaceGetDeviceCursor ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetDevicePositionMethodInfo ,
#endif
surfaceGetDevicePosition ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetDisplayMethodInfo ,
#endif
surfaceGetDisplay ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetFrameClockMethodInfo ,
#endif
surfaceGetFrameClock ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetHeightMethodInfo ,
#endif
surfaceGetHeight ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetMappedMethodInfo ,
#endif
surfaceGetMapped ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetScaleFactorMethodInfo ,
#endif
surfaceGetScaleFactor ,
#if defined(ENABLE_OVERLOADING)
SurfaceGetWidthMethodInfo ,
#endif
surfaceGetWidth ,
#if defined(ENABLE_OVERLOADING)
SurfaceHideMethodInfo ,
#endif
surfaceHide ,
#if defined(ENABLE_OVERLOADING)
SurfaceIsDestroyedMethodInfo ,
#endif
surfaceIsDestroyed ,
surfaceNewPopup ,
surfaceNewToplevel ,
#if defined(ENABLE_OVERLOADING)
SurfaceQueueRenderMethodInfo ,
#endif
surfaceQueueRender ,
#if defined(ENABLE_OVERLOADING)
SurfaceRequestLayoutMethodInfo ,
#endif
surfaceRequestLayout ,
#if defined(ENABLE_OVERLOADING)
SurfaceSetCursorMethodInfo ,
#endif
surfaceSetCursor ,
#if defined(ENABLE_OVERLOADING)
SurfaceSetDeviceCursorMethodInfo ,
#endif
surfaceSetDeviceCursor ,
#if defined(ENABLE_OVERLOADING)
SurfaceSetInputRegionMethodInfo ,
#endif
surfaceSetInputRegion ,
#if defined(ENABLE_OVERLOADING)
SurfaceSetOpaqueRegionMethodInfo ,
#endif
surfaceSetOpaqueRegion ,
#if defined(ENABLE_OVERLOADING)
SurfaceTranslateCoordinatesMethodInfo ,
#endif
surfaceTranslateCoordinates ,
#if defined(ENABLE_OVERLOADING)
SurfaceCursorPropertyInfo ,
#endif
clearSurfaceCursor ,
constructSurfaceCursor ,
getSurfaceCursor ,
setSurfaceCursor ,
#if defined(ENABLE_OVERLOADING)
surfaceCursor ,
#endif
#if defined(ENABLE_OVERLOADING)
SurfaceDisplayPropertyInfo ,
#endif
constructSurfaceDisplay ,
getSurfaceDisplay ,
#if defined(ENABLE_OVERLOADING)
surfaceDisplay ,
#endif
#if defined(ENABLE_OVERLOADING)
SurfaceFrameClockPropertyInfo ,
#endif
constructSurfaceFrameClock ,
getSurfaceFrameClock ,
#if defined(ENABLE_OVERLOADING)
surfaceFrameClock ,
#endif
#if defined(ENABLE_OVERLOADING)
SurfaceHeightPropertyInfo ,
#endif
getSurfaceHeight ,
#if defined(ENABLE_OVERLOADING)
surfaceHeight ,
#endif
#if defined(ENABLE_OVERLOADING)
SurfaceMappedPropertyInfo ,
#endif
getSurfaceMapped ,
#if defined(ENABLE_OVERLOADING)
surfaceMapped ,
#endif
#if defined(ENABLE_OVERLOADING)
SurfaceScaleFactorPropertyInfo ,
#endif
getSurfaceScaleFactor ,
#if defined(ENABLE_OVERLOADING)
surfaceScaleFactor ,
#endif
#if defined(ENABLE_OVERLOADING)
SurfaceWidthPropertyInfo ,
#endif
getSurfaceWidth ,
#if defined(ENABLE_OVERLOADING)
surfaceWidth ,
#endif
SurfaceEnterMonitorCallback ,
#if defined(ENABLE_OVERLOADING)
SurfaceEnterMonitorSignalInfo ,
#endif
afterSurfaceEnterMonitor ,
onSurfaceEnterMonitor ,
SurfaceEventCallback ,
#if defined(ENABLE_OVERLOADING)
SurfaceEventSignalInfo ,
#endif
afterSurfaceEvent ,
onSurfaceEvent ,
SurfaceLayoutCallback ,
#if defined(ENABLE_OVERLOADING)
SurfaceLayoutSignalInfo ,
#endif
afterSurfaceLayout ,
onSurfaceLayout ,
SurfaceLeaveMonitorCallback ,
#if defined(ENABLE_OVERLOADING)
SurfaceLeaveMonitorSignalInfo ,
#endif
afterSurfaceLeaveMonitor ,
onSurfaceLeaveMonitor ,
SurfaceRenderCallback ,
#if defined(ENABLE_OVERLOADING)
SurfaceRenderSignalInfo ,
#endif
afterSurfaceRender ,
onSurfaceRender ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.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
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
$c== :: Surface -> Surface -> Bool
== :: Surface -> Surface -> Bool
$c/= :: Surface -> Surface -> Bool
/= :: 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
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]
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 a. IO a -> m a
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
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 a. a -> IO a
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
type SurfaceEnterMonitorCallback =
Gdk.Monitor.Monitor
-> IO ()
type C_SurfaceEnterMonitorCallback =
Ptr Surface ->
Ptr Gdk.Monitor.Monitor ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_SurfaceEnterMonitorCallback :: C_SurfaceEnterMonitorCallback -> IO (FunPtr C_SurfaceEnterMonitorCallback)
wrap_SurfaceEnterMonitorCallback ::
GObject a => (a -> SurfaceEnterMonitorCallback) ->
C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback :: forall a.
GObject a =>
(a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback a -> SurfaceEnterMonitorCallback
gi'cb Ptr Surface
gi'selfPtr 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
Ptr Surface -> (Surface -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Surface
gi'selfPtr ((Surface -> IO ()) -> IO ()) -> (Surface -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Surface
gi'self -> a -> SurfaceEnterMonitorCallback
gi'cb (Surface -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Surface
gi'self) Monitor
monitor'
onSurfaceEnterMonitor :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceEnterMonitorCallback) -> m SignalHandlerId
onSurfaceEnterMonitor :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a
-> ((?self::a) => SurfaceEnterMonitorCallback) -> m SignalHandlerId
onSurfaceEnterMonitor a
obj (?self::a) => SurfaceEnterMonitorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceEnterMonitorCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceEnterMonitorCallback
SurfaceEnterMonitorCallback
cb
let wrapped' :: C_SurfaceEnterMonitorCallback
wrapped' = (a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
forall a.
GObject a =>
(a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback a -> SurfaceEnterMonitorCallback
wrapped
FunPtr C_SurfaceEnterMonitorCallback
wrapped'' <- C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceEnterMonitorCallback C_SurfaceEnterMonitorCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSurfaceEnterMonitor :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceEnterMonitorCallback) -> m SignalHandlerId
afterSurfaceEnterMonitor :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a
-> ((?self::a) => SurfaceEnterMonitorCallback) -> m SignalHandlerId
afterSurfaceEnterMonitor a
obj (?self::a) => SurfaceEnterMonitorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceEnterMonitorCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceEnterMonitorCallback
SurfaceEnterMonitorCallback
cb
let wrapped' :: C_SurfaceEnterMonitorCallback
wrapped' = (a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
forall a.
GObject a =>
(a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
wrap_SurfaceEnterMonitorCallback a -> SurfaceEnterMonitorCallback
wrapped
FunPtr C_SurfaceEnterMonitorCallback
wrapped'' <- C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceEnterMonitorCallback C_SurfaceEnterMonitorCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface::enter-monitor"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:signal:enterMonitor"})
#endif
type SurfaceEventCallback =
Gdk.Event.Event
-> IO Bool
type C_SurfaceEventCallback =
Ptr Surface ->
Ptr Gdk.Event.Event ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_SurfaceEventCallback :: C_SurfaceEventCallback -> IO (FunPtr C_SurfaceEventCallback)
wrap_SurfaceEventCallback ::
GObject a => (a -> SurfaceEventCallback) ->
C_SurfaceEventCallback
wrap_SurfaceEventCallback :: forall a.
GObject a =>
(a -> SurfaceEventCallback) -> C_SurfaceEventCallback
wrap_SurfaceEventCallback a -> SurfaceEventCallback
gi'cb Ptr Surface
gi'selfPtr 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 <- Ptr Surface -> (Surface -> IO Bool) -> IO Bool
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Surface
gi'selfPtr ((Surface -> IO Bool) -> IO Bool)
-> (Surface -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Surface
gi'self -> a -> SurfaceEventCallback
gi'cb (Surface -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Surface
gi'self) 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onSurfaceEvent :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceEventCallback) -> m SignalHandlerId
onSurfaceEvent :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> ((?self::a) => SurfaceEventCallback) -> m SignalHandlerId
onSurfaceEvent a
obj (?self::a) => SurfaceEventCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceEventCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceEventCallback
SurfaceEventCallback
cb
let wrapped' :: C_SurfaceEventCallback
wrapped' = (a -> SurfaceEventCallback) -> C_SurfaceEventCallback
forall a.
GObject a =>
(a -> SurfaceEventCallback) -> C_SurfaceEventCallback
wrap_SurfaceEventCallback a -> SurfaceEventCallback
wrapped
FunPtr C_SurfaceEventCallback
wrapped'' <- C_SurfaceEventCallback -> IO (FunPtr C_SurfaceEventCallback)
mk_SurfaceEventCallback C_SurfaceEventCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSurfaceEvent :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceEventCallback) -> m SignalHandlerId
afterSurfaceEvent :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> ((?self::a) => SurfaceEventCallback) -> m SignalHandlerId
afterSurfaceEvent a
obj (?self::a) => SurfaceEventCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceEventCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceEventCallback
SurfaceEventCallback
cb
let wrapped' :: C_SurfaceEventCallback
wrapped' = (a -> SurfaceEventCallback) -> C_SurfaceEventCallback
forall a.
GObject a =>
(a -> SurfaceEventCallback) -> C_SurfaceEventCallback
wrap_SurfaceEventCallback a -> SurfaceEventCallback
wrapped
FunPtr C_SurfaceEventCallback
wrapped'' <- C_SurfaceEventCallback -> IO (FunPtr C_SurfaceEventCallback)
mk_SurfaceEventCallback C_SurfaceEventCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface::event"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:signal:event"})
#endif
type SurfaceLayoutCallback =
Int32
-> Int32
-> IO ()
type C_SurfaceLayoutCallback =
Ptr Surface ->
Int32 ->
Int32 ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_SurfaceLayoutCallback :: C_SurfaceLayoutCallback -> IO (FunPtr C_SurfaceLayoutCallback)
wrap_SurfaceLayoutCallback ::
GObject a => (a -> SurfaceLayoutCallback) ->
C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback :: forall a.
GObject a =>
(a -> SurfaceLayoutCallback) -> C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback a -> SurfaceLayoutCallback
gi'cb Ptr Surface
gi'selfPtr Int32
width Int32
height Ptr ()
_ = do
Ptr Surface -> (Surface -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Surface
gi'selfPtr ((Surface -> IO ()) -> IO ()) -> (Surface -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Surface
gi'self -> a -> SurfaceLayoutCallback
gi'cb (Surface -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Surface
gi'self) Int32
width Int32
height
onSurfaceLayout :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceLayoutCallback) -> m SignalHandlerId
onSurfaceLayout :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> ((?self::a) => SurfaceLayoutCallback) -> m SignalHandlerId
onSurfaceLayout a
obj (?self::a) => SurfaceLayoutCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceLayoutCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceLayoutCallback
SurfaceLayoutCallback
cb
let wrapped' :: C_SurfaceLayoutCallback
wrapped' = (a -> SurfaceLayoutCallback) -> C_SurfaceLayoutCallback
forall a.
GObject a =>
(a -> SurfaceLayoutCallback) -> C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback a -> SurfaceLayoutCallback
wrapped
FunPtr C_SurfaceLayoutCallback
wrapped'' <- C_SurfaceLayoutCallback -> IO (FunPtr C_SurfaceLayoutCallback)
mk_SurfaceLayoutCallback C_SurfaceLayoutCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSurfaceLayout :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceLayoutCallback) -> m SignalHandlerId
afterSurfaceLayout :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> ((?self::a) => SurfaceLayoutCallback) -> m SignalHandlerId
afterSurfaceLayout a
obj (?self::a) => SurfaceLayoutCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceLayoutCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceLayoutCallback
SurfaceLayoutCallback
cb
let wrapped' :: C_SurfaceLayoutCallback
wrapped' = (a -> SurfaceLayoutCallback) -> C_SurfaceLayoutCallback
forall a.
GObject a =>
(a -> SurfaceLayoutCallback) -> C_SurfaceLayoutCallback
wrap_SurfaceLayoutCallback a -> SurfaceLayoutCallback
wrapped
FunPtr C_SurfaceLayoutCallback
wrapped'' <- C_SurfaceLayoutCallback -> IO (FunPtr C_SurfaceLayoutCallback)
mk_SurfaceLayoutCallback C_SurfaceLayoutCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface::layout"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:signal:layout"})
#endif
type SurfaceLeaveMonitorCallback =
Gdk.Monitor.Monitor
-> IO ()
type C_SurfaceLeaveMonitorCallback =
Ptr Surface ->
Ptr Gdk.Monitor.Monitor ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_SurfaceLeaveMonitorCallback :: C_SurfaceLeaveMonitorCallback -> IO (FunPtr C_SurfaceLeaveMonitorCallback)
wrap_SurfaceLeaveMonitorCallback ::
GObject a => (a -> SurfaceLeaveMonitorCallback) ->
C_SurfaceLeaveMonitorCallback
wrap_SurfaceLeaveMonitorCallback :: forall a.
GObject a =>
(a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
wrap_SurfaceLeaveMonitorCallback a -> SurfaceEnterMonitorCallback
gi'cb Ptr Surface
gi'selfPtr 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
Ptr Surface -> (Surface -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Surface
gi'selfPtr ((Surface -> IO ()) -> IO ()) -> (Surface -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Surface
gi'self -> a -> SurfaceEnterMonitorCallback
gi'cb (Surface -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Surface
gi'self) Monitor
monitor'
onSurfaceLeaveMonitor :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceLeaveMonitorCallback) -> m SignalHandlerId
onSurfaceLeaveMonitor :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a
-> ((?self::a) => SurfaceEnterMonitorCallback) -> m SignalHandlerId
onSurfaceLeaveMonitor a
obj (?self::a) => SurfaceEnterMonitorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceEnterMonitorCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceEnterMonitorCallback
SurfaceEnterMonitorCallback
cb
let wrapped' :: C_SurfaceEnterMonitorCallback
wrapped' = (a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
forall a.
GObject a =>
(a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
wrap_SurfaceLeaveMonitorCallback a -> SurfaceEnterMonitorCallback
wrapped
FunPtr C_SurfaceEnterMonitorCallback
wrapped'' <- C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceLeaveMonitorCallback C_SurfaceEnterMonitorCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSurfaceLeaveMonitor :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceLeaveMonitorCallback) -> m SignalHandlerId
afterSurfaceLeaveMonitor :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a
-> ((?self::a) => SurfaceEnterMonitorCallback) -> m SignalHandlerId
afterSurfaceLeaveMonitor a
obj (?self::a) => SurfaceEnterMonitorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceEnterMonitorCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceEnterMonitorCallback
SurfaceEnterMonitorCallback
cb
let wrapped' :: C_SurfaceEnterMonitorCallback
wrapped' = (a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
forall a.
GObject a =>
(a -> SurfaceEnterMonitorCallback) -> C_SurfaceEnterMonitorCallback
wrap_SurfaceLeaveMonitorCallback a -> SurfaceEnterMonitorCallback
wrapped
FunPtr C_SurfaceEnterMonitorCallback
wrapped'' <- C_SurfaceEnterMonitorCallback
-> IO (FunPtr C_SurfaceEnterMonitorCallback)
mk_SurfaceLeaveMonitorCallback C_SurfaceEnterMonitorCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface::leave-monitor"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:signal:leaveMonitor"})
#endif
type SurfaceRenderCallback =
Cairo.Region.Region
-> IO Bool
type C_SurfaceRenderCallback =
Ptr Surface ->
Ptr Cairo.Region.Region ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_SurfaceRenderCallback :: C_SurfaceRenderCallback -> IO (FunPtr C_SurfaceRenderCallback)
wrap_SurfaceRenderCallback ::
GObject a => (a -> SurfaceRenderCallback) ->
C_SurfaceRenderCallback
wrap_SurfaceRenderCallback :: forall a.
GObject a =>
(a -> SurfaceRenderCallback) -> C_SurfaceRenderCallback
wrap_SurfaceRenderCallback a -> SurfaceRenderCallback
gi'cb Ptr Surface
gi'selfPtr Ptr Region
region Ptr ()
_ = do
Ptr Region -> (Region -> IO CInt) -> IO CInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient 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 <- Ptr Surface -> (Surface -> IO Bool) -> IO Bool
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Surface
gi'selfPtr ((Surface -> IO Bool) -> IO Bool)
-> (Surface -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Surface
gi'self -> a -> SurfaceRenderCallback
gi'cb (Surface -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Surface
gi'self) 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onSurfaceRender :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceRenderCallback) -> m SignalHandlerId
onSurfaceRender :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> ((?self::a) => SurfaceRenderCallback) -> m SignalHandlerId
onSurfaceRender a
obj (?self::a) => SurfaceRenderCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceRenderCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceRenderCallback
SurfaceRenderCallback
cb
let wrapped' :: C_SurfaceRenderCallback
wrapped' = (a -> SurfaceRenderCallback) -> C_SurfaceRenderCallback
forall a.
GObject a =>
(a -> SurfaceRenderCallback) -> C_SurfaceRenderCallback
wrap_SurfaceRenderCallback a -> SurfaceRenderCallback
wrapped
FunPtr C_SurfaceRenderCallback
wrapped'' <- C_SurfaceRenderCallback -> IO (FunPtr C_SurfaceRenderCallback)
mk_SurfaceRenderCallback C_SurfaceRenderCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSurfaceRender :: (IsSurface a, MonadIO m) => a -> ((?self :: a) => SurfaceRenderCallback) -> m SignalHandlerId
afterSurfaceRender :: forall a (m :: * -> *).
(IsSurface a, MonadIO m) =>
a -> ((?self::a) => SurfaceRenderCallback) -> m SignalHandlerId
afterSurfaceRender a
obj (?self::a) => SurfaceRenderCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> SurfaceRenderCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SurfaceRenderCallback
SurfaceRenderCallback
cb
let wrapped' :: C_SurfaceRenderCallback
wrapped' = (a -> SurfaceRenderCallback) -> C_SurfaceRenderCallback
forall a.
GObject a =>
(a -> SurfaceRenderCallback) -> C_SurfaceRenderCallback
wrap_SurfaceRenderCallback a -> SurfaceRenderCallback
wrapped
FunPtr C_SurfaceRenderCallback
wrapped'' <- C_SurfaceRenderCallback -> IO (FunPtr C_SurfaceRenderCallback)
mk_SurfaceRenderCallback C_SurfaceRenderCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface::render"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:signal:render"})
#endif
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 a. IO a -> m a
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
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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"cursor" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"cursor" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearSurfaceCursor :: (MonadIO m, IsSurface o) => o -> m ()
clearSurfaceCursor :: forall (m :: * -> *) o. (MonadIO m, IsSurface o) => o -> m ()
clearSurfaceCursor o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe 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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.cursor"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:attr:cursor"
})
#endif
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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Display -> m Display) -> IO Display -> m Display
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Display) -> IO Display
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"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
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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"display" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data 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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.display"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:attr:display"
})
#endif
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 a. IO a -> m a
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
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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.frameClock"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:attr:frameClock"
})
#endif
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 a. IO a -> m a
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.height"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:attr:height"
})
#endif
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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.mapped"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:attr:mapped"
})
#endif
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 a. IO a -> m a
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.scaleFactor"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:attr:scaleFactor"
})
#endif
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 a. IO a -> m a
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.width"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#g:attr:width"
})
#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
foreign import ccall "gdk_surface_new_popup" ::
Ptr Surface ->
CInt ->
IO (Ptr Surface)
surfaceNewPopup ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> Bool
-> m Surface
a
parent Bool
autohide = IO Surface -> m Surface
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_surface_new_toplevel" gdk_surface_new_toplevel ::
Ptr Gdk.Display.Display ->
IO (Ptr Surface)
surfaceNewToplevel ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
a
-> m Surface
surfaceNewToplevel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Surface
surfaceNewToplevel a
display = IO Surface -> m Surface
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_surface_beep" gdk_surface_beep ::
Ptr Surface ->
IO ()
surfaceBeep ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m ()
surfaceBeep :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceBeep a
surface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceBeep",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceBeep"
})
#endif
foreign import ccall "gdk_surface_create_cairo_context" gdk_surface_create_cairo_context ::
Ptr Surface ->
IO (Ptr Gdk.CairoContext.CairoContext)
surfaceCreateCairoContext ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Gdk.CairoContext.CairoContext
surfaceCreateCairoContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m CairoContext
surfaceCreateCairoContext a
surface = IO CairoContext -> m CairoContext
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceCreateCairoContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceCreateCairoContext"
})
#endif
foreign import ccall "gdk_surface_create_gl_context" gdk_surface_create_gl_context ::
Ptr Surface ->
Ptr (Ptr GError) ->
IO (Ptr Gdk.GLContext.GLContext)
surfaceCreateGlContext ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Gdk.GLContext.GLContext
surfaceCreateGlContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m GLContext
surfaceCreateGlContext a
surface = IO GLContext -> m GLContext
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GLContext
result'
) (do
() -> IO ()
forall a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceCreateGlContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceCreateGlContext"
})
#endif
foreign import ccall "gdk_surface_create_similar_surface" gdk_surface_create_similar_surface ::
Ptr Surface ->
CUInt ->
Int32 ->
Int32 ->
IO (Ptr Cairo.Surface.Surface)
surfaceCreateSimilarSurface ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> Cairo.Enums.Content
-> Int32
-> Int32
-> m Cairo.Surface.Surface
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 a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceCreateSimilarSurface",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceCreateSimilarSurface"
})
#endif
foreign import ccall "gdk_surface_create_vulkan_context" gdk_surface_create_vulkan_context ::
Ptr Surface ->
Ptr (Ptr GError) ->
IO (Ptr Gdk.VulkanContext.VulkanContext)
surfaceCreateVulkanContext ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Gdk.VulkanContext.VulkanContext
surfaceCreateVulkanContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m VulkanContext
surfaceCreateVulkanContext a
surface = IO VulkanContext -> m VulkanContext
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return VulkanContext
result'
) (do
() -> IO ()
forall a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceCreateVulkanContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceCreateVulkanContext"
})
#endif
foreign import ccall "gdk_surface_destroy" gdk_surface_destroy ::
Ptr Surface ->
IO ()
surfaceDestroy ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m ()
surfaceDestroy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceDestroy a
surface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceDestroy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceDestroy"
})
#endif
foreign import ccall "gdk_surface_get_cursor" gdk_surface_get_cursor ::
Ptr Surface ->
IO (Ptr Gdk.Cursor.Cursor)
surfaceGetCursor ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m (Maybe Gdk.Cursor.Cursor)
surfaceGetCursor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m (Maybe Cursor)
surfaceGetCursor a
surface = IO (Maybe Cursor) -> m (Maybe Cursor)
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetCursor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetCursor"
})
#endif
foreign import ccall "gdk_surface_get_device_cursor" gdk_surface_get_device_cursor ::
Ptr Surface ->
Ptr Gdk.Device.Device ->
IO (Ptr Gdk.Cursor.Cursor)
surfaceGetDeviceCursor ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a, Gdk.Device.IsDevice b) =>
a
-> b
-> m (Maybe Gdk.Cursor.Cursor)
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 a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetDeviceCursor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetDeviceCursor"
})
#endif
foreign import ccall "gdk_surface_get_device_position" gdk_surface_get_device_position ::
Ptr Surface ->
Ptr Gdk.Device.Device ->
Ptr CDouble ->
Ptr CDouble ->
Ptr CUInt ->
IO CInt
surfaceGetDevicePosition ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a, Gdk.Device.IsDevice b) =>
a
-> b
-> m ((Bool, Double, Double, [Gdk.Flags.ModifierType]))
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 a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetDevicePosition",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetDevicePosition"
})
#endif
foreign import ccall "gdk_surface_get_display" gdk_surface_get_display ::
Ptr Surface ->
IO (Ptr Gdk.Display.Display)
surfaceGetDisplay ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Gdk.Display.Display
surfaceGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Display
surfaceGetDisplay a
surface = IO Display -> m Display
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Display -> m Display) -> IO Display -> m Display
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetDisplay",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetDisplay"
})
#endif
foreign import ccall "gdk_surface_get_frame_clock" gdk_surface_get_frame_clock ::
Ptr Surface ->
IO (Ptr Gdk.FrameClock.FrameClock)
surfaceGetFrameClock ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Gdk.FrameClock.FrameClock
surfaceGetFrameClock :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m FrameClock
surfaceGetFrameClock a
surface = IO FrameClock -> m FrameClock
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetFrameClock",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetFrameClock"
})
#endif
foreign import ccall "gdk_surface_get_height" gdk_surface_get_height ::
Ptr Surface ->
IO Int32
surfaceGetHeight ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Int32
surfaceGetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Int32
surfaceGetHeight a
surface = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetHeight",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetHeight"
})
#endif
foreign import ccall "gdk_surface_get_mapped" gdk_surface_get_mapped ::
Ptr Surface ->
IO CInt
surfaceGetMapped ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Bool
surfaceGetMapped :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Bool
surfaceGetMapped a
surface = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetMapped",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetMapped"
})
#endif
foreign import ccall "gdk_surface_get_scale_factor" gdk_surface_get_scale_factor ::
Ptr Surface ->
IO Int32
surfaceGetScaleFactor ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Int32
surfaceGetScaleFactor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Int32
surfaceGetScaleFactor a
surface = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetScaleFactor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetScaleFactor"
})
#endif
foreign import ccall "gdk_surface_get_width" gdk_surface_get_width ::
Ptr Surface ->
IO Int32
surfaceGetWidth ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Int32
surfaceGetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Int32
surfaceGetWidth a
surface = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceGetWidth",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceGetWidth"
})
#endif
foreign import ccall "gdk_surface_hide" gdk_surface_hide ::
Ptr Surface ->
IO ()
surfaceHide ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m ()
surfaceHide :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceHide a
surface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceHide",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceHide"
})
#endif
foreign import ccall "gdk_surface_is_destroyed" gdk_surface_is_destroyed ::
Ptr Surface ->
IO CInt
surfaceIsDestroyed ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m Bool
surfaceIsDestroyed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m Bool
surfaceIsDestroyed a
surface = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceIsDestroyed",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceIsDestroyed"
})
#endif
foreign import ccall "gdk_surface_queue_render" gdk_surface_queue_render ::
Ptr Surface ->
IO ()
surfaceQueueRender ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m ()
surfaceQueueRender :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceQueueRender a
surface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceQueueRender",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceQueueRender"
})
#endif
foreign import ccall "gdk_surface_request_layout" gdk_surface_request_layout ::
Ptr Surface ->
IO ()
surfaceRequestLayout ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> m ()
surfaceRequestLayout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> m ()
surfaceRequestLayout a
surface = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceRequestLayout",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceRequestLayout"
})
#endif
foreign import ccall "gdk_surface_set_cursor" gdk_surface_set_cursor ::
Ptr Surface ->
Ptr Gdk.Cursor.Cursor ->
IO ()
surfaceSetCursor ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a, Gdk.Cursor.IsCursor b) =>
a
-> Maybe (b)
-> 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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceSetCursor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceSetCursor"
})
#endif
foreign import ccall "gdk_surface_set_device_cursor" gdk_surface_set_device_cursor ::
Ptr Surface ->
Ptr Gdk.Device.Device ->
Ptr Gdk.Cursor.Cursor ->
IO ()
surfaceSetDeviceCursor ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a, Gdk.Device.IsDevice b, Gdk.Cursor.IsCursor c) =>
a
-> b
-> c
-> 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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceSetDeviceCursor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceSetDeviceCursor"
})
#endif
foreign import ccall "gdk_surface_set_input_region" gdk_surface_set_input_region ::
Ptr Surface ->
Ptr Cairo.Region.Region ->
IO ()
surfaceSetInputRegion ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> Cairo.Region.Region
-> m ()
surfaceSetInputRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> Region -> m ()
surfaceSetInputRegion a
surface Region
region = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceSetInputRegion",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceSetInputRegion"
})
#endif
foreign import ccall "gdk_surface_set_opaque_region" gdk_surface_set_opaque_region ::
Ptr Surface ->
Ptr Cairo.Region.Region ->
IO ()
surfaceSetOpaqueRegion ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a) =>
a
-> Maybe (Cairo.Region.Region)
-> m ()
surfaceSetOpaqueRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSurface a) =>
a -> Maybe Region -> m ()
surfaceSetOpaqueRegion a
surface Maybe Region
region = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceSetOpaqueRegion",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceSetOpaqueRegion"
})
#endif
foreign import ccall "gdk_surface_translate_coordinates" gdk_surface_translate_coordinates ::
Ptr Surface ->
Ptr Surface ->
Ptr CDouble ->
Ptr CDouble ->
IO CInt
surfaceTranslateCoordinates ::
(B.CallStack.HasCallStack, MonadIO m, IsSurface a, IsSurface b) =>
a
-> b
-> Double
-> Double
-> m ((Bool, Double, Double))
surfaceTranslateCoordinates :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSurface a, IsSurface b) =>
a -> b -> Double -> Double -> m (Bool, Double, Double)
surfaceTranslateCoordinates a
from b
to Double
x Double
y = IO (Bool, Double, Double) -> m (Bool, Double, Double)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Double, Double) -> m (Bool, Double, Double))
-> IO (Bool, Double, Double) -> m (Bool, Double, Double)
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
Ptr CDouble
x'' <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CDouble
x'' CDouble
x'
let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
Ptr CDouble
y'' <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CDouble
y'' CDouble
y'
CInt
result <- Ptr Surface -> Ptr Surface -> Ptr CDouble -> Ptr CDouble -> IO CInt
gdk_surface_translate_coordinates Ptr Surface
from' Ptr Surface
to' Ptr CDouble
x'' Ptr CDouble
y''
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'''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
from
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
to
Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
x''
Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
y''
(Bool, Double, Double) -> IO (Bool, Double, Double)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Double
x'''', Double
y'''')
#if defined(ENABLE_OVERLOADING)
data SurfaceTranslateCoordinatesMethodInfo
instance (signature ~ (b -> Double -> Double -> m ((Bool, Double, Double))), MonadIO m, IsSurface a, IsSurface b) => O.OverloadedMethod SurfaceTranslateCoordinatesMethodInfo a signature where
overloadedMethod = surfaceTranslateCoordinates
instance O.OverloadedMethodInfo SurfaceTranslateCoordinatesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Surface.surfaceTranslateCoordinates",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Objects-Surface.html#v:surfaceTranslateCoordinates"
})
#endif