{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.Cursor
(
Cursor(..) ,
IsCursor ,
toCursor ,
#if defined(ENABLE_OVERLOADING)
ResolveCursorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
CursorGetCursorTypeMethodInfo ,
#endif
cursorGetCursorType ,
#if defined(ENABLE_OVERLOADING)
CursorGetDisplayMethodInfo ,
#endif
cursorGetDisplay ,
#if defined(ENABLE_OVERLOADING)
CursorGetImageMethodInfo ,
#endif
cursorGetImage ,
#if defined(ENABLE_OVERLOADING)
CursorGetSurfaceMethodInfo ,
#endif
cursorGetSurface ,
cursorNew ,
cursorNewForDisplay ,
cursorNewFromName ,
cursorNewFromPixbuf ,
cursorNewFromSurface ,
#if defined(ENABLE_OVERLOADING)
CursorRefMethodInfo ,
#endif
cursorRef ,
#if defined(ENABLE_OVERLOADING)
CursorUnrefMethodInfo ,
#endif
cursorUnref ,
#if defined(ENABLE_OVERLOADING)
CursorCursorTypePropertyInfo ,
#endif
constructCursorCursorType ,
#if defined(ENABLE_OVERLOADING)
cursorCursorType ,
#endif
getCursorCursorType ,
#if defined(ENABLE_OVERLOADING)
CursorDisplayPropertyInfo ,
#endif
constructCursorDisplay ,
#if defined(ENABLE_OVERLOADING)
cursorDisplay ,
#endif
getCursorDisplay ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Pattern as Cairo.Pattern
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Callbacks as Gdk.Callbacks
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceManager as Gdk.DeviceManager
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.DragContext as Gdk.DragContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawingContext as Gdk.DrawingContext
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.Screen as Gdk.Screen
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Visual as Gdk.Visual
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
import {-# SOURCE #-} qualified GI.Gdk.Structs.Color as Gdk.Color
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventDND as Gdk.EventDND
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadAxis as Gdk.EventPadAxis
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadButton as Gdk.EventPadButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadGroupMode as Gdk.EventPadGroupMode
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSetting as Gdk.EventSetting
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouch as Gdk.EventTouch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadPinch as Gdk.EventTouchpadPinch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadSwipe as Gdk.EventTouchpadSwipe
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import {-# SOURCE #-} qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.WindowAttr as Gdk.WindowAttr
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext
#else
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
#endif
newtype Cursor = Cursor (SP.ManagedPtr Cursor)
deriving (Cursor -> Cursor -> Bool
(Cursor -> Cursor -> Bool)
-> (Cursor -> Cursor -> Bool) -> Eq Cursor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cursor -> Cursor -> Bool
== :: Cursor -> Cursor -> Bool
$c/= :: Cursor -> Cursor -> Bool
/= :: Cursor -> Cursor -> Bool
Eq)
instance SP.ManagedPtrNewtype Cursor where
toManagedPtr :: Cursor -> ManagedPtr Cursor
toManagedPtr (Cursor ManagedPtr Cursor
p) = ManagedPtr Cursor
p
foreign import ccall "gdk_cursor_get_type"
c_gdk_cursor_get_type :: IO B.Types.GType
instance B.Types.TypedObject Cursor where
glibType :: IO GType
glibType = IO GType
c_gdk_cursor_get_type
instance B.Types.GObject Cursor
class (SP.GObject o, O.IsDescendantOf Cursor o) => IsCursor o
instance (SP.GObject o, O.IsDescendantOf Cursor o) => IsCursor o
instance O.HasParentTypes Cursor
type instance O.ParentTypes Cursor = '[GObject.Object.Object]
toCursor :: (MIO.MonadIO m, IsCursor o) => o -> m Cursor
toCursor :: forall (m :: * -> *) o. (MonadIO m, IsCursor o) => o -> m Cursor
toCursor = IO Cursor -> m Cursor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Cursor -> m Cursor) -> (o -> IO Cursor) -> o -> m Cursor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Cursor -> Cursor) -> o -> IO Cursor
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Cursor -> Cursor
Cursor
instance B.GValue.IsGValue (Maybe Cursor) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_cursor_get_type
gvalueSet_ :: Ptr GValue -> Maybe Cursor -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Cursor
P.Nothing = Ptr GValue -> Ptr Cursor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Cursor
forall a. Ptr a
FP.nullPtr :: FP.Ptr Cursor)
gvalueSet_ Ptr GValue
gv (P.Just Cursor
obj) = Cursor -> (Ptr Cursor -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Cursor
obj (Ptr GValue -> Ptr Cursor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Cursor)
gvalueGet_ Ptr GValue
gv = do
Ptr Cursor
ptr <- Ptr GValue -> IO (Ptr Cursor)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Cursor)
if Ptr Cursor
ptr Ptr Cursor -> Ptr Cursor -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Cursor
forall a. Ptr a
FP.nullPtr
then Cursor -> Maybe Cursor
forall a. a -> Maybe a
P.Just (Cursor -> Maybe Cursor) -> IO Cursor -> IO (Maybe Cursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Cursor -> Cursor) -> Ptr Cursor -> IO Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Cursor -> Cursor
Cursor Ptr Cursor
ptr
else Maybe Cursor -> IO (Maybe Cursor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Cursor
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveCursorMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveCursorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveCursorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveCursorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveCursorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveCursorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveCursorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveCursorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveCursorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveCursorMethod "ref" o = CursorRefMethodInfo
ResolveCursorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveCursorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveCursorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveCursorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveCursorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveCursorMethod "unref" o = CursorUnrefMethodInfo
ResolveCursorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveCursorMethod "getCursorType" o = CursorGetCursorTypeMethodInfo
ResolveCursorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveCursorMethod "getDisplay" o = CursorGetDisplayMethodInfo
ResolveCursorMethod "getImage" o = CursorGetImageMethodInfo
ResolveCursorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveCursorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveCursorMethod "getSurface" o = CursorGetSurfaceMethodInfo
ResolveCursorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveCursorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveCursorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveCursorMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveCursorMethod t Cursor, O.OverloadedMethod info Cursor p) => OL.IsLabel t (Cursor -> 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 ~ ResolveCursorMethod t Cursor, O.OverloadedMethod info Cursor p, R.HasField t Cursor p) => R.HasField t Cursor p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveCursorMethod t Cursor, O.OverloadedMethodInfo info Cursor) => OL.IsLabel t (O.MethodProxy info Cursor) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getCursorCursorType :: (MonadIO m, IsCursor o) => o -> m Gdk.Enums.CursorType
getCursorCursorType :: forall (m :: * -> *) o.
(MonadIO m, IsCursor o) =>
o -> m CursorType
getCursorCursorType o
obj = IO CursorType -> m CursorType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CursorType -> m CursorType) -> IO CursorType -> m CursorType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CursorType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"cursor-type"
constructCursorCursorType :: (IsCursor o, MIO.MonadIO m) => Gdk.Enums.CursorType -> m (GValueConstruct o)
constructCursorCursorType :: forall o (m :: * -> *).
(IsCursor o, MonadIO m) =>
CursorType -> m (GValueConstruct o)
constructCursorCursorType CursorType
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 -> CursorType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"cursor-type" CursorType
val
#if defined(ENABLE_OVERLOADING)
data CursorCursorTypePropertyInfo
instance AttrInfo CursorCursorTypePropertyInfo where
type AttrAllowedOps CursorCursorTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint CursorCursorTypePropertyInfo = IsCursor
type AttrSetTypeConstraint CursorCursorTypePropertyInfo = (~) Gdk.Enums.CursorType
type AttrTransferTypeConstraint CursorCursorTypePropertyInfo = (~) Gdk.Enums.CursorType
type AttrTransferType CursorCursorTypePropertyInfo = Gdk.Enums.CursorType
type AttrGetType CursorCursorTypePropertyInfo = Gdk.Enums.CursorType
type AttrLabel CursorCursorTypePropertyInfo = "cursor-type"
type AttrOrigin CursorCursorTypePropertyInfo = Cursor
attrGet = getCursorCursorType
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructCursorCursorType
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Cursor.cursorType"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Cursor.html#g:attr:cursorType"
})
#endif
getCursorDisplay :: (MonadIO m, IsCursor o) => o -> m Gdk.Display.Display
getCursorDisplay :: forall (m :: * -> *) o. (MonadIO m, IsCursor o) => o -> m Display
getCursorDisplay 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
"getCursorDisplay" (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
constructCursorDisplay :: (IsCursor o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructCursorDisplay :: forall o (m :: * -> *) a.
(IsCursor o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructCursorDisplay 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 CursorDisplayPropertyInfo
instance AttrInfo CursorDisplayPropertyInfo where
type AttrAllowedOps CursorDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CursorDisplayPropertyInfo = IsCursor
type AttrSetTypeConstraint CursorDisplayPropertyInfo = Gdk.Display.IsDisplay
type AttrTransferTypeConstraint CursorDisplayPropertyInfo = Gdk.Display.IsDisplay
type AttrTransferType CursorDisplayPropertyInfo = Gdk.Display.Display
type AttrGetType CursorDisplayPropertyInfo = Gdk.Display.Display
type AttrLabel CursorDisplayPropertyInfo = "display"
type AttrOrigin CursorDisplayPropertyInfo = Cursor
attrGet = getCursorDisplay
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gdk.Display.Display v
attrConstruct = constructCursorDisplay
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Cursor.display"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Cursor.html#g:attr:display"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Cursor
type instance O.AttributeList Cursor = CursorAttributeList
type CursorAttributeList = ('[ '("cursorType", CursorCursorTypePropertyInfo), '("display", CursorDisplayPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
cursorCursorType :: AttrLabelProxy "cursorType"
cursorCursorType = AttrLabelProxy
cursorDisplay :: AttrLabelProxy "display"
cursorDisplay = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Cursor = CursorSignalList
type CursorSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gdk_cursor_new" gdk_cursor_new ::
CInt ->
IO (Ptr Cursor)
{-# DEPRECATED cursorNew ["(Since version 3.16)","Use 'GI.Gdk.Objects.Cursor.cursorNewForDisplay' instead."] #-}
cursorNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Gdk.Enums.CursorType
-> m Cursor
cursorNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CursorType -> m Cursor
cursorNew CursorType
cursorType = IO Cursor -> m Cursor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Cursor -> m Cursor) -> IO Cursor -> m Cursor
forall a b. (a -> b) -> a -> b
$ do
let cursorType' :: CInt
cursorType' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (CursorType -> Int) -> CursorType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CursorType -> Int
forall a. Enum a => a -> Int
fromEnum) CursorType
cursorType
Ptr Cursor
result <- CInt -> IO (Ptr Cursor)
gdk_cursor_new CInt
cursorType'
Text -> Ptr Cursor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cursorNew" Ptr Cursor
result
Cursor
result' <- ((ManagedPtr Cursor -> Cursor) -> Ptr Cursor -> IO Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Cursor -> Cursor
Cursor) Ptr Cursor
result
Cursor -> IO Cursor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Cursor
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_cursor_new_for_display" gdk_cursor_new_for_display ::
Ptr Gdk.Display.Display ->
CInt ->
IO (Ptr Cursor)
cursorNewForDisplay ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
a
-> Gdk.Enums.CursorType
-> m (Maybe Cursor)
cursorNewForDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> CursorType -> m (Maybe Cursor)
cursorNewForDisplay a
display CursorType
cursorType = 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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
let cursorType' :: CInt
cursorType' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (CursorType -> Int) -> CursorType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CursorType -> Int
forall a. Enum a => a -> Int
fromEnum) CursorType
cursorType
Ptr Cursor
result <- Ptr Display -> CInt -> IO (Ptr Cursor)
gdk_cursor_new_for_display Ptr Display
display' CInt
cursorType'
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
wrapObject ManagedPtr Cursor -> 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
display
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)
#endif
foreign import ccall "gdk_cursor_new_from_name" gdk_cursor_new_from_name ::
Ptr Gdk.Display.Display ->
CString ->
IO (Ptr Cursor)
cursorNewFromName ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
a
-> T.Text
-> m (Maybe Cursor)
cursorNewFromName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Text -> m (Maybe Cursor)
cursorNewFromName a
display Text
name = 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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CString
name' <- Text -> IO CString
textToCString Text
name
Ptr Cursor
result <- Ptr Display -> CString -> IO (Ptr Cursor)
gdk_cursor_new_from_name Ptr Display
display' CString
name'
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
wrapObject ManagedPtr Cursor -> 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
display
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
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)
#endif
foreign import ccall "gdk_cursor_new_from_pixbuf" gdk_cursor_new_from_pixbuf ::
Ptr Gdk.Display.Display ->
Ptr GdkPixbuf.Pixbuf.Pixbuf ->
Int32 ->
Int32 ->
IO (Ptr Cursor)
cursorNewFromPixbuf ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a, GdkPixbuf.Pixbuf.IsPixbuf b) =>
a
-> b
-> Int32
-> Int32
-> m Cursor
cursorNewFromPixbuf :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDisplay a, IsPixbuf b) =>
a -> b -> Int32 -> Int32 -> m Cursor
cursorNewFromPixbuf a
display b
pixbuf Int32
x Int32
y = IO Cursor -> m Cursor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Cursor -> m Cursor) -> IO Cursor -> m Cursor
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 Pixbuf
pixbuf' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
pixbuf
Ptr Cursor
result <- Ptr Display -> Ptr Pixbuf -> Int32 -> Int32 -> IO (Ptr Cursor)
gdk_cursor_new_from_pixbuf Ptr Display
display' Ptr Pixbuf
pixbuf' Int32
x Int32
y
Text -> Ptr Cursor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cursorNewFromPixbuf" Ptr Cursor
result
Cursor
result' <- ((ManagedPtr Cursor -> Cursor) -> Ptr Cursor -> IO Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Cursor -> Cursor
Cursor) Ptr Cursor
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
pixbuf
Cursor -> IO Cursor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Cursor
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_cursor_new_from_surface" gdk_cursor_new_from_surface ::
Ptr Gdk.Display.Display ->
Ptr Cairo.Surface.Surface ->
CDouble ->
CDouble ->
IO (Ptr Cursor)
cursorNewFromSurface ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
a
-> Cairo.Surface.Surface
-> Double
-> Double
-> m Cursor
cursorNewFromSurface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Surface -> Double -> Double -> m Cursor
cursorNewFromSurface a
display Surface
surface Double
x Double
y = IO Cursor -> m Cursor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Cursor -> m Cursor) -> IO Cursor -> m Cursor
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
surface' <- Surface -> IO (Ptr Surface)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Surface
surface
let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
Ptr Cursor
result <- Ptr Display -> Ptr Surface -> CDouble -> CDouble -> IO (Ptr Cursor)
gdk_cursor_new_from_surface Ptr Display
display' Ptr Surface
surface' CDouble
x' CDouble
y'
Text -> Ptr Cursor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cursorNewFromSurface" Ptr Cursor
result
Cursor
result' <- ((ManagedPtr Cursor -> Cursor) -> Ptr Cursor -> IO Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Cursor -> Cursor
Cursor) Ptr Cursor
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Surface -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Surface
surface
Cursor -> IO Cursor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Cursor
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_cursor_get_cursor_type" gdk_cursor_get_cursor_type ::
Ptr Cursor ->
IO CInt
cursorGetCursorType ::
(B.CallStack.HasCallStack, MonadIO m, IsCursor a) =>
a
-> m Gdk.Enums.CursorType
cursorGetCursorType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCursor a) =>
a -> m CursorType
cursorGetCursorType a
cursor = IO CursorType -> m CursorType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CursorType -> m CursorType) -> IO CursorType -> m CursorType
forall a b. (a -> b) -> a -> b
$ do
Ptr Cursor
cursor' <- a -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cursor
CInt
result <- Ptr Cursor -> IO CInt
gdk_cursor_get_cursor_type Ptr Cursor
cursor'
let result' :: CursorType
result' = (Int -> CursorType
forall a. Enum a => Int -> a
toEnum (Int -> CursorType) -> (CInt -> Int) -> CInt -> CursorType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cursor
CursorType -> IO CursorType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CursorType
result'
#if defined(ENABLE_OVERLOADING)
data CursorGetCursorTypeMethodInfo
instance (signature ~ (m Gdk.Enums.CursorType), MonadIO m, IsCursor a) => O.OverloadedMethod CursorGetCursorTypeMethodInfo a signature where
overloadedMethod = cursorGetCursorType
instance O.OverloadedMethodInfo CursorGetCursorTypeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Cursor.cursorGetCursorType",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Cursor.html#v:cursorGetCursorType"
})
#endif
foreign import ccall "gdk_cursor_get_display" gdk_cursor_get_display ::
Ptr Cursor ->
IO (Ptr Gdk.Display.Display)
cursorGetDisplay ::
(B.CallStack.HasCallStack, MonadIO m, IsCursor a) =>
a
-> m Gdk.Display.Display
cursorGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCursor a) =>
a -> m Display
cursorGetDisplay a
cursor = 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 Cursor
cursor' <- a -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cursor
Ptr Display
result <- Ptr Cursor -> IO (Ptr Display)
gdk_cursor_get_display Ptr Cursor
cursor'
Text -> Ptr Display -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cursorGetDisplay" 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
cursor
Display -> IO Display
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result'
#if defined(ENABLE_OVERLOADING)
data CursorGetDisplayMethodInfo
instance (signature ~ (m Gdk.Display.Display), MonadIO m, IsCursor a) => O.OverloadedMethod CursorGetDisplayMethodInfo a signature where
overloadedMethod = cursorGetDisplay
instance O.OverloadedMethodInfo CursorGetDisplayMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Cursor.cursorGetDisplay",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Cursor.html#v:cursorGetDisplay"
})
#endif
foreign import ccall "gdk_cursor_get_image" gdk_cursor_get_image ::
Ptr Cursor ->
IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
cursorGetImage ::
(B.CallStack.HasCallStack, MonadIO m, IsCursor a) =>
a
-> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
cursorGetImage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCursor a) =>
a -> m (Maybe Pixbuf)
cursorGetImage a
cursor = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
Ptr Cursor
cursor' <- a -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cursor
Ptr Pixbuf
result <- Ptr Cursor -> IO (Ptr Pixbuf)
gdk_cursor_get_image Ptr Cursor
cursor'
Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result'
Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cursor
Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
#if defined(ENABLE_OVERLOADING)
data CursorGetImageMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m, IsCursor a) => O.OverloadedMethod CursorGetImageMethodInfo a signature where
overloadedMethod = cursorGetImage
instance O.OverloadedMethodInfo CursorGetImageMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Cursor.cursorGetImage",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Cursor.html#v:cursorGetImage"
})
#endif
foreign import ccall "gdk_cursor_get_surface" gdk_cursor_get_surface ::
Ptr Cursor ->
Ptr CDouble ->
Ptr CDouble ->
IO (Ptr Cairo.Surface.Surface)
cursorGetSurface ::
(B.CallStack.HasCallStack, MonadIO m, IsCursor a) =>
a
-> m ((Maybe Cairo.Surface.Surface, Double, Double))
cursorGetSurface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCursor a) =>
a -> m (Maybe Surface, Double, Double)
cursorGetSurface a
cursor = IO (Maybe Surface, Double, Double)
-> m (Maybe Surface, Double, Double)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Surface, Double, Double)
-> m (Maybe Surface, Double, Double))
-> IO (Maybe Surface, Double, Double)
-> m (Maybe Surface, Double, Double)
forall a b. (a -> b) -> a -> b
$ do
Ptr Cursor
cursor' <- a -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cursor
Ptr CDouble
xHot <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
Ptr CDouble
yHot <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
Ptr Surface
result <- Ptr Cursor -> Ptr CDouble -> Ptr CDouble -> IO (Ptr Surface)
gdk_cursor_get_surface Ptr Cursor
cursor' Ptr CDouble
xHot Ptr CDouble
yHot
Maybe Surface
maybeResult <- Ptr Surface -> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Surface
result ((Ptr Surface -> IO Surface) -> IO (Maybe Surface))
-> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ \Ptr Surface
result' -> do
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'
Surface -> IO Surface
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result''
CDouble
xHot' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
xHot
let xHot'' :: Double
xHot'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
xHot'
CDouble
yHot' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
yHot
let yHot'' :: Double
yHot'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
yHot'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cursor
Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
xHot
Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
yHot
(Maybe Surface, Double, Double)
-> IO (Maybe Surface, Double, Double)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Surface
maybeResult, Double
xHot'', Double
yHot'')
#if defined(ENABLE_OVERLOADING)
data CursorGetSurfaceMethodInfo
instance (signature ~ (m ((Maybe Cairo.Surface.Surface, Double, Double))), MonadIO m, IsCursor a) => O.OverloadedMethod CursorGetSurfaceMethodInfo a signature where
overloadedMethod = cursorGetSurface
instance O.OverloadedMethodInfo CursorGetSurfaceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Cursor.cursorGetSurface",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Cursor.html#v:cursorGetSurface"
})
#endif
foreign import ccall "gdk_cursor_ref" gdk_cursor_ref ::
Ptr Cursor ->
IO (Ptr Cursor)
{-# DEPRECATED cursorRef ["(Since version 3.0)","Use 'GI.GObject.Objects.Object.objectRef' instead"] #-}
cursorRef ::
(B.CallStack.HasCallStack, MonadIO m, IsCursor a) =>
a
-> m Cursor
cursorRef :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCursor a) =>
a -> m Cursor
cursorRef a
cursor = IO Cursor -> m Cursor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Cursor -> m Cursor) -> IO Cursor -> m Cursor
forall a b. (a -> b) -> a -> b
$ do
Ptr Cursor
cursor' <- a -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cursor
Ptr Cursor
result <- Ptr Cursor -> IO (Ptr Cursor)
gdk_cursor_ref Ptr Cursor
cursor'
Text -> Ptr Cursor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cursorRef" Ptr Cursor
result
Cursor
result' <- ((ManagedPtr Cursor -> Cursor) -> Ptr Cursor -> IO Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Cursor -> Cursor
Cursor) Ptr Cursor
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cursor
Cursor -> IO Cursor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Cursor
result'
#if defined(ENABLE_OVERLOADING)
data CursorRefMethodInfo
instance (signature ~ (m Cursor), MonadIO m, IsCursor a) => O.OverloadedMethod CursorRefMethodInfo a signature where
overloadedMethod = cursorRef
instance O.OverloadedMethodInfo CursorRefMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Cursor.cursorRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Cursor.html#v:cursorRef"
})
#endif
foreign import ccall "gdk_cursor_unref" gdk_cursor_unref ::
Ptr Cursor ->
IO ()
{-# DEPRECATED cursorUnref ["(Since version 3.0)","Use 'GI.GObject.Objects.Object.objectUnref' instead"] #-}
cursorUnref ::
(B.CallStack.HasCallStack, MonadIO m, IsCursor a) =>
a
-> m ()
cursorUnref :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCursor a) =>
a -> m ()
cursorUnref a
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 Cursor
cursor' <- a -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cursor
Ptr Cursor -> IO ()
gdk_cursor_unref Ptr Cursor
cursor'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cursor
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data CursorUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m, IsCursor a) => O.OverloadedMethod CursorUnrefMethodInfo a signature where
overloadedMethod = cursorUnref
instance O.OverloadedMethodInfo CursorUnrefMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Cursor.cursorUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Cursor.html#v:cursorUnref"
})
#endif