{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkGestureStylus@ is a @GtkGesture@ specific to stylus input.
-- 
-- The provided signals just relay the basic information of the
-- stylus events.

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

module GI.Gtk.Objects.GestureStylus
    ( 
#if defined(ENABLE_OVERLOADING)
    GestureStylusGetAxesMethodInfo          ,
#endif

-- * Exported types
    GestureStylus(..)                       ,
    IsGestureStylus                         ,
    toGestureStylus                         ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [group]("GI.Gtk.Objects.Gesture#g:method:group"), [handlesSequence]("GI.Gtk.Objects.Gesture#g:method:handlesSequence"), [isActive]("GI.Gtk.Objects.Gesture#g:method:isActive"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isGroupedWith]("GI.Gtk.Objects.Gesture#g:method:isGroupedWith"), [isRecognized]("GI.Gtk.Objects.Gesture#g:method:isRecognized"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [reset]("GI.Gtk.Objects.EventController#g:method:reset"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [ungroup]("GI.Gtk.Objects.Gesture#g:method:ungroup"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAxes]("GI.Gtk.Objects.GestureStylus#g:method:getAxes"), [getAxis]("GI.Gtk.Objects.GestureStylus#g:method:getAxis"), [getBacklog]("GI.Gtk.Objects.GestureStylus#g:method:getBacklog"), [getBoundingBox]("GI.Gtk.Objects.Gesture#g:method:getBoundingBox"), [getBoundingBoxCenter]("GI.Gtk.Objects.Gesture#g:method:getBoundingBoxCenter"), [getButton]("GI.Gtk.Objects.GestureSingle#g:method:getButton"), [getCurrentButton]("GI.Gtk.Objects.GestureSingle#g:method:getCurrentButton"), [getCurrentEvent]("GI.Gtk.Objects.EventController#g:method:getCurrentEvent"), [getCurrentEventDevice]("GI.Gtk.Objects.EventController#g:method:getCurrentEventDevice"), [getCurrentEventState]("GI.Gtk.Objects.EventController#g:method:getCurrentEventState"), [getCurrentEventTime]("GI.Gtk.Objects.EventController#g:method:getCurrentEventTime"), [getCurrentSequence]("GI.Gtk.Objects.GestureSingle#g:method:getCurrentSequence"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDevice]("GI.Gtk.Objects.Gesture#g:method:getDevice"), [getDeviceTool]("GI.Gtk.Objects.GestureStylus#g:method:getDeviceTool"), [getExclusive]("GI.Gtk.Objects.GestureSingle#g:method:getExclusive"), [getGroup]("GI.Gtk.Objects.Gesture#g:method:getGroup"), [getLastEvent]("GI.Gtk.Objects.Gesture#g:method:getLastEvent"), [getLastUpdatedSequence]("GI.Gtk.Objects.Gesture#g:method:getLastUpdatedSequence"), [getName]("GI.Gtk.Objects.EventController#g:method:getName"), [getPoint]("GI.Gtk.Objects.Gesture#g:method:getPoint"), [getPropagationLimit]("GI.Gtk.Objects.EventController#g:method:getPropagationLimit"), [getPropagationPhase]("GI.Gtk.Objects.EventController#g:method:getPropagationPhase"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSequenceState]("GI.Gtk.Objects.Gesture#g:method:getSequenceState"), [getSequences]("GI.Gtk.Objects.Gesture#g:method:getSequences"), [getStylusOnly]("GI.Gtk.Objects.GestureStylus#g:method:getStylusOnly"), [getTouchOnly]("GI.Gtk.Objects.GestureSingle#g:method:getTouchOnly"), [getWidget]("GI.Gtk.Objects.EventController#g:method:getWidget").
-- 
-- ==== Setters
-- [setButton]("GI.Gtk.Objects.GestureSingle#g:method:setButton"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setExclusive]("GI.Gtk.Objects.GestureSingle#g:method:setExclusive"), [setName]("GI.Gtk.Objects.EventController#g:method:setName"), [setPropagationLimit]("GI.Gtk.Objects.EventController#g:method:setPropagationLimit"), [setPropagationPhase]("GI.Gtk.Objects.EventController#g:method:setPropagationPhase"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSequenceState]("GI.Gtk.Objects.Gesture#g:method:setSequenceState"), [setState]("GI.Gtk.Objects.Gesture#g:method:setState"), [setStaticName]("GI.Gtk.Objects.EventController#g:method:setStaticName"), [setStylusOnly]("GI.Gtk.Objects.GestureStylus#g:method:setStylusOnly"), [setTouchOnly]("GI.Gtk.Objects.GestureSingle#g:method:setTouchOnly").

#if defined(ENABLE_OVERLOADING)
    ResolveGestureStylusMethod              ,
#endif

-- ** getAxis #method:getAxis#

#if defined(ENABLE_OVERLOADING)
    GestureStylusGetAxisMethodInfo          ,
#endif
    gestureStylusGetAxis                    ,


-- ** getBacklog #method:getBacklog#

#if defined(ENABLE_OVERLOADING)
    GestureStylusGetBacklogMethodInfo       ,
#endif
    gestureStylusGetBacklog                 ,


-- ** getDeviceTool #method:getDeviceTool#

#if defined(ENABLE_OVERLOADING)
    GestureStylusGetDeviceToolMethodInfo    ,
#endif
    gestureStylusGetDeviceTool              ,


-- ** getStylusOnly #method:getStylusOnly#

#if defined(ENABLE_OVERLOADING)
    GestureStylusGetStylusOnlyMethodInfo    ,
#endif
    gestureStylusGetStylusOnly              ,


-- ** new #method:new#

    gestureStylusNew                        ,


-- ** setStylusOnly #method:setStylusOnly#

#if defined(ENABLE_OVERLOADING)
    GestureStylusSetStylusOnlyMethodInfo    ,
#endif
    gestureStylusSetStylusOnly              ,




 -- * Properties


-- ** stylusOnly #attr:stylusOnly#
-- | If this gesture should exclusively react to stylus input devices.
-- 
-- /Since: 4.10/

#if defined(ENABLE_OVERLOADING)
    GestureStylusStylusOnlyPropertyInfo     ,
#endif
    constructGestureStylusStylusOnly        ,
#if defined(ENABLE_OVERLOADING)
    gestureStylusStylusOnly                 ,
#endif
    getGestureStylusStylusOnly              ,
    setGestureStylusStylusOnly              ,




 -- * Signals


-- ** down #signal:down#

    GestureStylusDownCallback               ,
#if defined(ENABLE_OVERLOADING)
    GestureStylusDownSignalInfo             ,
#endif
    afterGestureStylusDown                  ,
    onGestureStylusDown                     ,


-- ** motion #signal:motion#

    GestureStylusMotionCallback             ,
#if defined(ENABLE_OVERLOADING)
    GestureStylusMotionSignalInfo           ,
#endif
    afterGestureStylusMotion                ,
    onGestureStylusMotion                   ,


-- ** proximity #signal:proximity#

    GestureStylusProximityCallback          ,
#if defined(ENABLE_OVERLOADING)
    GestureStylusProximitySignalInfo        ,
#endif
    afterGestureStylusProximity             ,
    onGestureStylusProximity                ,


-- ** up #signal:up#

    GestureStylusUpCallback                 ,
#if defined(ENABLE_OVERLOADING)
    GestureStylusUpSignalInfo               ,
#endif
    afterGestureStylusUp                    ,
    onGestureStylusUp                       ,




    ) 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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Enums as Gdk.Enums
import qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import qualified GI.Gdk.Structs.TimeCoord as Gdk.TimeCoord
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.Gesture as Gtk.Gesture
import {-# SOURCE #-} qualified GI.Gtk.Objects.GestureSingle as Gtk.GestureSingle

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

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

foreign import ccall "gtk_gesture_stylus_get_type"
    c_gtk_gesture_stylus_get_type :: IO B.Types.GType

instance B.Types.TypedObject GestureStylus where
    glibType :: IO GType
glibType = IO GType
c_gtk_gesture_stylus_get_type

instance B.Types.GObject GestureStylus

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

instance O.HasParentTypes GestureStylus
type instance O.ParentTypes GestureStylus = '[Gtk.GestureSingle.GestureSingle, Gtk.Gesture.Gesture, Gtk.EventController.EventController, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveGestureStylusMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveGestureStylusMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGestureStylusMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGestureStylusMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGestureStylusMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGestureStylusMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGestureStylusMethod "group" o = Gtk.Gesture.GestureGroupMethodInfo
    ResolveGestureStylusMethod "handlesSequence" o = Gtk.Gesture.GestureHandlesSequenceMethodInfo
    ResolveGestureStylusMethod "isActive" o = Gtk.Gesture.GestureIsActiveMethodInfo
    ResolveGestureStylusMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGestureStylusMethod "isGroupedWith" o = Gtk.Gesture.GestureIsGroupedWithMethodInfo
    ResolveGestureStylusMethod "isRecognized" o = Gtk.Gesture.GestureIsRecognizedMethodInfo
    ResolveGestureStylusMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGestureStylusMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGestureStylusMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGestureStylusMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGestureStylusMethod "reset" o = Gtk.EventController.EventControllerResetMethodInfo
    ResolveGestureStylusMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGestureStylusMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGestureStylusMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGestureStylusMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGestureStylusMethod "ungroup" o = Gtk.Gesture.GestureUngroupMethodInfo
    ResolveGestureStylusMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGestureStylusMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGestureStylusMethod "getAxes" o = GestureStylusGetAxesMethodInfo
    ResolveGestureStylusMethod "getAxis" o = GestureStylusGetAxisMethodInfo
    ResolveGestureStylusMethod "getBacklog" o = GestureStylusGetBacklogMethodInfo
    ResolveGestureStylusMethod "getBoundingBox" o = Gtk.Gesture.GestureGetBoundingBoxMethodInfo
    ResolveGestureStylusMethod "getBoundingBoxCenter" o = Gtk.Gesture.GestureGetBoundingBoxCenterMethodInfo
    ResolveGestureStylusMethod "getButton" o = Gtk.GestureSingle.GestureSingleGetButtonMethodInfo
    ResolveGestureStylusMethod "getCurrentButton" o = Gtk.GestureSingle.GestureSingleGetCurrentButtonMethodInfo
    ResolveGestureStylusMethod "getCurrentEvent" o = Gtk.EventController.EventControllerGetCurrentEventMethodInfo
    ResolveGestureStylusMethod "getCurrentEventDevice" o = Gtk.EventController.EventControllerGetCurrentEventDeviceMethodInfo
    ResolveGestureStylusMethod "getCurrentEventState" o = Gtk.EventController.EventControllerGetCurrentEventStateMethodInfo
    ResolveGestureStylusMethod "getCurrentEventTime" o = Gtk.EventController.EventControllerGetCurrentEventTimeMethodInfo
    ResolveGestureStylusMethod "getCurrentSequence" o = Gtk.GestureSingle.GestureSingleGetCurrentSequenceMethodInfo
    ResolveGestureStylusMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGestureStylusMethod "getDevice" o = Gtk.Gesture.GestureGetDeviceMethodInfo
    ResolveGestureStylusMethod "getDeviceTool" o = GestureStylusGetDeviceToolMethodInfo
    ResolveGestureStylusMethod "getExclusive" o = Gtk.GestureSingle.GestureSingleGetExclusiveMethodInfo
    ResolveGestureStylusMethod "getGroup" o = Gtk.Gesture.GestureGetGroupMethodInfo
    ResolveGestureStylusMethod "getLastEvent" o = Gtk.Gesture.GestureGetLastEventMethodInfo
    ResolveGestureStylusMethod "getLastUpdatedSequence" o = Gtk.Gesture.GestureGetLastUpdatedSequenceMethodInfo
    ResolveGestureStylusMethod "getName" o = Gtk.EventController.EventControllerGetNameMethodInfo
    ResolveGestureStylusMethod "getPoint" o = Gtk.Gesture.GestureGetPointMethodInfo
    ResolveGestureStylusMethod "getPropagationLimit" o = Gtk.EventController.EventControllerGetPropagationLimitMethodInfo
    ResolveGestureStylusMethod "getPropagationPhase" o = Gtk.EventController.EventControllerGetPropagationPhaseMethodInfo
    ResolveGestureStylusMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGestureStylusMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGestureStylusMethod "getSequenceState" o = Gtk.Gesture.GestureGetSequenceStateMethodInfo
    ResolveGestureStylusMethod "getSequences" o = Gtk.Gesture.GestureGetSequencesMethodInfo
    ResolveGestureStylusMethod "getStylusOnly" o = GestureStylusGetStylusOnlyMethodInfo
    ResolveGestureStylusMethod "getTouchOnly" o = Gtk.GestureSingle.GestureSingleGetTouchOnlyMethodInfo
    ResolveGestureStylusMethod "getWidget" o = Gtk.EventController.EventControllerGetWidgetMethodInfo
    ResolveGestureStylusMethod "setButton" o = Gtk.GestureSingle.GestureSingleSetButtonMethodInfo
    ResolveGestureStylusMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGestureStylusMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGestureStylusMethod "setExclusive" o = Gtk.GestureSingle.GestureSingleSetExclusiveMethodInfo
    ResolveGestureStylusMethod "setName" o = Gtk.EventController.EventControllerSetNameMethodInfo
    ResolveGestureStylusMethod "setPropagationLimit" o = Gtk.EventController.EventControllerSetPropagationLimitMethodInfo
    ResolveGestureStylusMethod "setPropagationPhase" o = Gtk.EventController.EventControllerSetPropagationPhaseMethodInfo
    ResolveGestureStylusMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGestureStylusMethod "setSequenceState" o = Gtk.Gesture.GestureSetSequenceStateMethodInfo
    ResolveGestureStylusMethod "setState" o = Gtk.Gesture.GestureSetStateMethodInfo
    ResolveGestureStylusMethod "setStaticName" o = Gtk.EventController.EventControllerSetStaticNameMethodInfo
    ResolveGestureStylusMethod "setStylusOnly" o = GestureStylusSetStylusOnlyMethodInfo
    ResolveGestureStylusMethod "setTouchOnly" o = Gtk.GestureSingle.GestureSingleSetTouchOnlyMethodInfo
    ResolveGestureStylusMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal GestureStylus::down
-- | Emitted when the stylus touches the device.
type GestureStylusDownCallback =
    Double
    -- ^ /@x@/: the X coordinate of the stylus event
    -> Double
    -- ^ /@y@/: the Y coordinate of the stylus event
    -> IO ()

type C_GestureStylusDownCallback =
    Ptr GestureStylus ->                    -- object
    CDouble ->
    CDouble ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_GestureStylusDownCallback :: 
    GObject a => (a -> GestureStylusDownCallback) ->
    C_GestureStylusDownCallback
wrap_GestureStylusDownCallback :: forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusDownCallback a -> GestureStylusDownCallback
gi'cb Ptr GestureStylus
gi'selfPtr CDouble
x CDouble
y Ptr ()
_ = do
    let x' :: Double
x' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x
    let y' :: Double
y' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y
    Ptr GestureStylus -> (GestureStylus -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr GestureStylus
gi'selfPtr ((GestureStylus -> IO ()) -> IO ())
-> (GestureStylus -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \GestureStylus
gi'self -> a -> GestureStylusDownCallback
gi'cb (GestureStylus -> a
forall a b. Coercible a b => a -> b
Coerce.coerce GestureStylus
gi'self)  Double
x' Double
y'


-- | Connect a signal handler for the [down](#signal:down) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' gestureStylus #down callback
-- @
-- 
-- 
onGestureStylusDown :: (IsGestureStylus a, MonadIO m) => a -> ((?self :: a) => GestureStylusDownCallback) -> m SignalHandlerId
onGestureStylusDown :: forall a (m :: * -> *).
(IsGestureStylus a, MonadIO m) =>
a -> ((?self::a) => GestureStylusDownCallback) -> m SignalHandlerId
onGestureStylusDown a
obj (?self::a) => GestureStylusDownCallback
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 -> GestureStylusDownCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => GestureStylusDownCallback
GestureStylusDownCallback
cb
    let wrapped' :: C_GestureStylusDownCallback
wrapped' = (a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusDownCallback a -> GestureStylusDownCallback
wrapped
    FunPtr C_GestureStylusDownCallback
wrapped'' <- C_GestureStylusDownCallback
-> IO (FunPtr C_GestureStylusDownCallback)
mk_GestureStylusDownCallback C_GestureStylusDownCallback
wrapped'
    a
-> Text
-> FunPtr C_GestureStylusDownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"down" FunPtr C_GestureStylusDownCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [down](#signal:down) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' gestureStylus #down callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterGestureStylusDown :: (IsGestureStylus a, MonadIO m) => a -> ((?self :: a) => GestureStylusDownCallback) -> m SignalHandlerId
afterGestureStylusDown :: forall a (m :: * -> *).
(IsGestureStylus a, MonadIO m) =>
a -> ((?self::a) => GestureStylusDownCallback) -> m SignalHandlerId
afterGestureStylusDown a
obj (?self::a) => GestureStylusDownCallback
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 -> GestureStylusDownCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => GestureStylusDownCallback
GestureStylusDownCallback
cb
    let wrapped' :: C_GestureStylusDownCallback
wrapped' = (a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusDownCallback a -> GestureStylusDownCallback
wrapped
    FunPtr C_GestureStylusDownCallback
wrapped'' <- C_GestureStylusDownCallback
-> IO (FunPtr C_GestureStylusDownCallback)
mk_GestureStylusDownCallback C_GestureStylusDownCallback
wrapped'
    a
-> Text
-> FunPtr C_GestureStylusDownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"down" FunPtr C_GestureStylusDownCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data GestureStylusDownSignalInfo
instance SignalInfo GestureStylusDownSignalInfo where
    type HaskellCallbackType GestureStylusDownSignalInfo = GestureStylusDownCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_GestureStylusDownCallback cb
        cb'' <- mk_GestureStylusDownCallback cb'
        connectSignalFunPtr obj "down" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus::down"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#g:signal:down"})

#endif

-- signal GestureStylus::motion
-- | Emitted when the stylus moves while touching the device.
type GestureStylusMotionCallback =
    Double
    -- ^ /@x@/: the X coordinate of the stylus event
    -> Double
    -- ^ /@y@/: the Y coordinate of the stylus event
    -> IO ()

type C_GestureStylusMotionCallback =
    Ptr GestureStylus ->                    -- object
    CDouble ->
    CDouble ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_GestureStylusMotionCallback :: 
    GObject a => (a -> GestureStylusMotionCallback) ->
    C_GestureStylusMotionCallback
wrap_GestureStylusMotionCallback :: forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusMotionCallback a -> GestureStylusDownCallback
gi'cb Ptr GestureStylus
gi'selfPtr CDouble
x CDouble
y Ptr ()
_ = do
    let x' :: Double
x' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x
    let y' :: Double
y' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y
    Ptr GestureStylus -> (GestureStylus -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr GestureStylus
gi'selfPtr ((GestureStylus -> IO ()) -> IO ())
-> (GestureStylus -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \GestureStylus
gi'self -> a -> GestureStylusDownCallback
gi'cb (GestureStylus -> a
forall a b. Coercible a b => a -> b
Coerce.coerce GestureStylus
gi'self)  Double
x' Double
y'


-- | Connect a signal handler for the [motion](#signal:motion) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' gestureStylus #motion callback
-- @
-- 
-- 
onGestureStylusMotion :: (IsGestureStylus a, MonadIO m) => a -> ((?self :: a) => GestureStylusMotionCallback) -> m SignalHandlerId
onGestureStylusMotion :: forall a (m :: * -> *).
(IsGestureStylus a, MonadIO m) =>
a -> ((?self::a) => GestureStylusDownCallback) -> m SignalHandlerId
onGestureStylusMotion a
obj (?self::a) => GestureStylusDownCallback
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 -> GestureStylusDownCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => GestureStylusDownCallback
GestureStylusDownCallback
cb
    let wrapped' :: C_GestureStylusDownCallback
wrapped' = (a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusMotionCallback a -> GestureStylusDownCallback
wrapped
    FunPtr C_GestureStylusDownCallback
wrapped'' <- C_GestureStylusDownCallback
-> IO (FunPtr C_GestureStylusDownCallback)
mk_GestureStylusMotionCallback C_GestureStylusDownCallback
wrapped'
    a
-> Text
-> FunPtr C_GestureStylusDownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"motion" FunPtr C_GestureStylusDownCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [motion](#signal:motion) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' gestureStylus #motion callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterGestureStylusMotion :: (IsGestureStylus a, MonadIO m) => a -> ((?self :: a) => GestureStylusMotionCallback) -> m SignalHandlerId
afterGestureStylusMotion :: forall a (m :: * -> *).
(IsGestureStylus a, MonadIO m) =>
a -> ((?self::a) => GestureStylusDownCallback) -> m SignalHandlerId
afterGestureStylusMotion a
obj (?self::a) => GestureStylusDownCallback
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 -> GestureStylusDownCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => GestureStylusDownCallback
GestureStylusDownCallback
cb
    let wrapped' :: C_GestureStylusDownCallback
wrapped' = (a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusMotionCallback a -> GestureStylusDownCallback
wrapped
    FunPtr C_GestureStylusDownCallback
wrapped'' <- C_GestureStylusDownCallback
-> IO (FunPtr C_GestureStylusDownCallback)
mk_GestureStylusMotionCallback C_GestureStylusDownCallback
wrapped'
    a
-> Text
-> FunPtr C_GestureStylusDownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"motion" FunPtr C_GestureStylusDownCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data GestureStylusMotionSignalInfo
instance SignalInfo GestureStylusMotionSignalInfo where
    type HaskellCallbackType GestureStylusMotionSignalInfo = GestureStylusMotionCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_GestureStylusMotionCallback cb
        cb'' <- mk_GestureStylusMotionCallback cb'
        connectSignalFunPtr obj "motion" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus::motion"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#g:signal:motion"})

#endif

-- signal GestureStylus::proximity
-- | Emitted when the stylus is in proximity of the device.
type GestureStylusProximityCallback =
    Double
    -- ^ /@x@/: the X coordinate of the stylus event
    -> Double
    -- ^ /@y@/: the Y coordinate of the stylus event
    -> IO ()

type C_GestureStylusProximityCallback =
    Ptr GestureStylus ->                    -- object
    CDouble ->
    CDouble ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_GestureStylusProximityCallback :: 
    GObject a => (a -> GestureStylusProximityCallback) ->
    C_GestureStylusProximityCallback
wrap_GestureStylusProximityCallback :: forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusProximityCallback a -> GestureStylusDownCallback
gi'cb Ptr GestureStylus
gi'selfPtr CDouble
x CDouble
y Ptr ()
_ = do
    let x' :: Double
x' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x
    let y' :: Double
y' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y
    Ptr GestureStylus -> (GestureStylus -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr GestureStylus
gi'selfPtr ((GestureStylus -> IO ()) -> IO ())
-> (GestureStylus -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \GestureStylus
gi'self -> a -> GestureStylusDownCallback
gi'cb (GestureStylus -> a
forall a b. Coercible a b => a -> b
Coerce.coerce GestureStylus
gi'self)  Double
x' Double
y'


-- | Connect a signal handler for the [proximity](#signal:proximity) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' gestureStylus #proximity callback
-- @
-- 
-- 
onGestureStylusProximity :: (IsGestureStylus a, MonadIO m) => a -> ((?self :: a) => GestureStylusProximityCallback) -> m SignalHandlerId
onGestureStylusProximity :: forall a (m :: * -> *).
(IsGestureStylus a, MonadIO m) =>
a -> ((?self::a) => GestureStylusDownCallback) -> m SignalHandlerId
onGestureStylusProximity a
obj (?self::a) => GestureStylusDownCallback
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 -> GestureStylusDownCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => GestureStylusDownCallback
GestureStylusDownCallback
cb
    let wrapped' :: C_GestureStylusDownCallback
wrapped' = (a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusProximityCallback a -> GestureStylusDownCallback
wrapped
    FunPtr C_GestureStylusDownCallback
wrapped'' <- C_GestureStylusDownCallback
-> IO (FunPtr C_GestureStylusDownCallback)
mk_GestureStylusProximityCallback C_GestureStylusDownCallback
wrapped'
    a
-> Text
-> FunPtr C_GestureStylusDownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"proximity" FunPtr C_GestureStylusDownCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [proximity](#signal:proximity) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' gestureStylus #proximity callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterGestureStylusProximity :: (IsGestureStylus a, MonadIO m) => a -> ((?self :: a) => GestureStylusProximityCallback) -> m SignalHandlerId
afterGestureStylusProximity :: forall a (m :: * -> *).
(IsGestureStylus a, MonadIO m) =>
a -> ((?self::a) => GestureStylusDownCallback) -> m SignalHandlerId
afterGestureStylusProximity a
obj (?self::a) => GestureStylusDownCallback
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 -> GestureStylusDownCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => GestureStylusDownCallback
GestureStylusDownCallback
cb
    let wrapped' :: C_GestureStylusDownCallback
wrapped' = (a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusProximityCallback a -> GestureStylusDownCallback
wrapped
    FunPtr C_GestureStylusDownCallback
wrapped'' <- C_GestureStylusDownCallback
-> IO (FunPtr C_GestureStylusDownCallback)
mk_GestureStylusProximityCallback C_GestureStylusDownCallback
wrapped'
    a
-> Text
-> FunPtr C_GestureStylusDownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"proximity" FunPtr C_GestureStylusDownCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data GestureStylusProximitySignalInfo
instance SignalInfo GestureStylusProximitySignalInfo where
    type HaskellCallbackType GestureStylusProximitySignalInfo = GestureStylusProximityCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_GestureStylusProximityCallback cb
        cb'' <- mk_GestureStylusProximityCallback cb'
        connectSignalFunPtr obj "proximity" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus::proximity"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#g:signal:proximity"})

#endif

-- signal GestureStylus::up
-- | Emitted when the stylus no longer touches the device.
type GestureStylusUpCallback =
    Double
    -- ^ /@x@/: the X coordinate of the stylus event
    -> Double
    -- ^ /@y@/: the Y coordinate of the stylus event
    -> IO ()

type C_GestureStylusUpCallback =
    Ptr GestureStylus ->                    -- object
    CDouble ->
    CDouble ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_GestureStylusUpCallback :: 
    GObject a => (a -> GestureStylusUpCallback) ->
    C_GestureStylusUpCallback
wrap_GestureStylusUpCallback :: forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusUpCallback a -> GestureStylusDownCallback
gi'cb Ptr GestureStylus
gi'selfPtr CDouble
x CDouble
y Ptr ()
_ = do
    let x' :: Double
x' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x
    let y' :: Double
y' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y
    Ptr GestureStylus -> (GestureStylus -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr GestureStylus
gi'selfPtr ((GestureStylus -> IO ()) -> IO ())
-> (GestureStylus -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \GestureStylus
gi'self -> a -> GestureStylusDownCallback
gi'cb (GestureStylus -> a
forall a b. Coercible a b => a -> b
Coerce.coerce GestureStylus
gi'self)  Double
x' Double
y'


-- | Connect a signal handler for the [up](#signal:up) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' gestureStylus #up callback
-- @
-- 
-- 
onGestureStylusUp :: (IsGestureStylus a, MonadIO m) => a -> ((?self :: a) => GestureStylusUpCallback) -> m SignalHandlerId
onGestureStylusUp :: forall a (m :: * -> *).
(IsGestureStylus a, MonadIO m) =>
a -> ((?self::a) => GestureStylusDownCallback) -> m SignalHandlerId
onGestureStylusUp a
obj (?self::a) => GestureStylusDownCallback
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 -> GestureStylusDownCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => GestureStylusDownCallback
GestureStylusDownCallback
cb
    let wrapped' :: C_GestureStylusDownCallback
wrapped' = (a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusUpCallback a -> GestureStylusDownCallback
wrapped
    FunPtr C_GestureStylusDownCallback
wrapped'' <- C_GestureStylusDownCallback
-> IO (FunPtr C_GestureStylusDownCallback)
mk_GestureStylusUpCallback C_GestureStylusDownCallback
wrapped'
    a
-> Text
-> FunPtr C_GestureStylusDownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"up" FunPtr C_GestureStylusDownCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [up](#signal:up) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' gestureStylus #up callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterGestureStylusUp :: (IsGestureStylus a, MonadIO m) => a -> ((?self :: a) => GestureStylusUpCallback) -> m SignalHandlerId
afterGestureStylusUp :: forall a (m :: * -> *).
(IsGestureStylus a, MonadIO m) =>
a -> ((?self::a) => GestureStylusDownCallback) -> m SignalHandlerId
afterGestureStylusUp a
obj (?self::a) => GestureStylusDownCallback
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 -> GestureStylusDownCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => GestureStylusDownCallback
GestureStylusDownCallback
cb
    let wrapped' :: C_GestureStylusDownCallback
wrapped' = (a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
forall a.
GObject a =>
(a -> GestureStylusDownCallback) -> C_GestureStylusDownCallback
wrap_GestureStylusUpCallback a -> GestureStylusDownCallback
wrapped
    FunPtr C_GestureStylusDownCallback
wrapped'' <- C_GestureStylusDownCallback
-> IO (FunPtr C_GestureStylusDownCallback)
mk_GestureStylusUpCallback C_GestureStylusDownCallback
wrapped'
    a
-> Text
-> FunPtr C_GestureStylusDownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"up" FunPtr C_GestureStylusDownCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data GestureStylusUpSignalInfo
instance SignalInfo GestureStylusUpSignalInfo where
    type HaskellCallbackType GestureStylusUpSignalInfo = GestureStylusUpCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_GestureStylusUpCallback cb
        cb'' <- mk_GestureStylusUpCallback cb'
        connectSignalFunPtr obj "up" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus::up"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#g:signal:up"})

#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data GestureStylusStylusOnlyPropertyInfo
instance AttrInfo GestureStylusStylusOnlyPropertyInfo where
    type AttrAllowedOps GestureStylusStylusOnlyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GestureStylusStylusOnlyPropertyInfo = IsGestureStylus
    type AttrSetTypeConstraint GestureStylusStylusOnlyPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint GestureStylusStylusOnlyPropertyInfo = (~) Bool
    type AttrTransferType GestureStylusStylusOnlyPropertyInfo = Bool
    type AttrGetType GestureStylusStylusOnlyPropertyInfo = Bool
    type AttrLabel GestureStylusStylusOnlyPropertyInfo = "stylus-only"
    type AttrOrigin GestureStylusStylusOnlyPropertyInfo = GestureStylus
    attrGet = getGestureStylusStylusOnly
    attrSet = setGestureStylusStylusOnly
    attrTransfer _ v = do
        return v
    attrConstruct = constructGestureStylusStylusOnly
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus.stylusOnly"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#g:attr:stylusOnly"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GestureStylus
type instance O.AttributeList GestureStylus = GestureStylusAttributeList
type GestureStylusAttributeList = ('[ '("button", Gtk.GestureSingle.GestureSingleButtonPropertyInfo), '("exclusive", Gtk.GestureSingle.GestureSingleExclusivePropertyInfo), '("nPoints", Gtk.Gesture.GestureNPointsPropertyInfo), '("name", Gtk.EventController.EventControllerNamePropertyInfo), '("propagationLimit", Gtk.EventController.EventControllerPropagationLimitPropertyInfo), '("propagationPhase", Gtk.EventController.EventControllerPropagationPhasePropertyInfo), '("stylusOnly", GestureStylusStylusOnlyPropertyInfo), '("touchOnly", Gtk.GestureSingle.GestureSingleTouchOnlyPropertyInfo), '("widget", Gtk.EventController.EventControllerWidgetPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
gestureStylusStylusOnly :: AttrLabelProxy "stylusOnly"
gestureStylusStylusOnly = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GestureStylus = GestureStylusSignalList
type GestureStylusSignalList = ('[ '("begin", Gtk.Gesture.GestureBeginSignalInfo), '("cancel", Gtk.Gesture.GestureCancelSignalInfo), '("down", GestureStylusDownSignalInfo), '("end", Gtk.Gesture.GestureEndSignalInfo), '("motion", GestureStylusMotionSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("proximity", GestureStylusProximitySignalInfo), '("sequenceStateChanged", Gtk.Gesture.GestureSequenceStateChangedSignalInfo), '("up", GestureStylusUpSignalInfo), '("update", Gtk.Gesture.GestureUpdateSignalInfo)] :: [(Symbol, DK.Type)])

#endif

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

foreign import ccall "gtk_gesture_stylus_new" gtk_gesture_stylus_new :: 
    IO (Ptr GestureStylus)

-- | Creates a new @GtkGestureStylus@.
gestureStylusNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m GestureStylus
    -- ^ __Returns:__ a newly created stylus gesture
gestureStylusNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m GestureStylus
gestureStylusNew  = IO GestureStylus -> m GestureStylus
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GestureStylus -> m GestureStylus)
-> IO GestureStylus -> m GestureStylus
forall a b. (a -> b) -> a -> b
$ do
    Ptr GestureStylus
result <- IO (Ptr GestureStylus)
gtk_gesture_stylus_new
    Text -> Ptr GestureStylus -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"gestureStylusNew" Ptr GestureStylus
result
    GestureStylus
result' <- ((ManagedPtr GestureStylus -> GestureStylus)
-> Ptr GestureStylus -> IO GestureStylus
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr GestureStylus -> GestureStylus
GestureStylus) Ptr GestureStylus
result
    GestureStylus -> IO GestureStylus
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GestureStylus
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- XXX Could not generate method GestureStylus::get_axes
{-  Bad introspection data: `TCArray False (-1) (-1) (TBasicType TDouble)' is an array type, but contains no length information,
    so it cannot be unpacked.
-}
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data GestureStylusGetAxesMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "getAxes" GestureStylus) => O.OverloadedMethod GestureStylusGetAxesMethodInfo o p where
    overloadedMethod = undefined

instance (o ~ O.UnsupportedMethodError "getAxes" GestureStylus) => O.OverloadedMethodInfo GestureStylusGetAxesMethodInfo o where
    overloadedMethodInfo = undefined

#endif

-- method GestureStylus::get_axis
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "gesture"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GestureStylus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkGestureStylus`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "axis"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "AxisUse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "requested device axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the axis value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_gesture_stylus_get_axis" gtk_gesture_stylus_get_axis :: 
    Ptr GestureStylus ->                    -- gesture : TInterface (Name {namespace = "Gtk", name = "GestureStylus"})
    CUInt ->                                -- axis : TInterface (Name {namespace = "Gdk", name = "AxisUse"})
    Ptr CDouble ->                          -- value : TBasicType TDouble
    IO CInt

-- | Returns the current value for the requested /@axis@/.
-- 
-- This function must be called from the handler of one of the
-- [GestureStylus::down]("GI.Gtk.Objects.GestureStylus#g:signal:down"), [GestureStylus::motion]("GI.Gtk.Objects.GestureStylus#g:signal:motion"),
-- [GestureStylus::up]("GI.Gtk.Objects.GestureStylus#g:signal:up") or [GestureStylus::proximity]("GI.Gtk.Objects.GestureStylus#g:signal:proximity")
-- signals.
gestureStylusGetAxis ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureStylus a) =>
    a
    -- ^ /@gesture@/: a @GtkGestureStylus@
    -> Gdk.Enums.AxisUse
    -- ^ /@axis@/: requested device axis
    -> m ((Bool, Double))
    -- ^ __Returns:__ 'P.True' if there is a current value for the axis
gestureStylusGetAxis :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureStylus a) =>
a -> AxisUse -> m (Bool, Double)
gestureStylusGetAxis a
gesture AxisUse
axis = IO (Bool, Double) -> m (Bool, Double)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Double) -> m (Bool, Double))
-> IO (Bool, Double) -> m (Bool, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GestureStylus
gesture' <- a -> IO (Ptr GestureStylus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    let axis' :: CUInt
axis' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (AxisUse -> Int) -> AxisUse -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AxisUse -> Int
forall a. Enum a => a -> Int
fromEnum) AxisUse
axis
    Ptr CDouble
value <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    CInt
result <- Ptr GestureStylus -> CUInt -> Ptr CDouble -> IO CInt
gtk_gesture_stylus_get_axis Ptr GestureStylus
gesture' CUInt
axis' Ptr CDouble
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    CDouble
value' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
value
    let value'' :: Double
value'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gesture
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
value
    (Bool, Double) -> IO (Bool, Double)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Double
value'')

#if defined(ENABLE_OVERLOADING)
data GestureStylusGetAxisMethodInfo
instance (signature ~ (Gdk.Enums.AxisUse -> m ((Bool, Double))), MonadIO m, IsGestureStylus a) => O.OverloadedMethod GestureStylusGetAxisMethodInfo a signature where
    overloadedMethod = gestureStylusGetAxis

instance O.OverloadedMethodInfo GestureStylusGetAxisMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus.gestureStylusGetAxis",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#v:gestureStylusGetAxis"
        })


#endif

-- method GestureStylus::get_backlog
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "gesture"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GestureStylus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkGestureStylus`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "backlog"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gdk" , name = "TimeCoord" })
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "coordinates and times for the backlog events"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "n_elems"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the number of elements"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_elems"
--              , argType = TBasicType TUInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "return location for the number of elements"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_gesture_stylus_get_backlog" gtk_gesture_stylus_get_backlog :: 
    Ptr GestureStylus ->                    -- gesture : TInterface (Name {namespace = "Gtk", name = "GestureStylus"})
    Ptr (Ptr Gdk.TimeCoord.TimeCoord) ->    -- backlog : TCArray False (-1) 2 (TInterface (Name {namespace = "Gdk", name = "TimeCoord"}))
    Ptr Word32 ->                           -- n_elems : TBasicType TUInt
    IO CInt

-- | Returns the accumulated backlog of tracking information.
-- 
-- By default, GTK will limit rate of input events. On stylus input
-- where accuracy of strokes is paramount, this function returns the
-- accumulated coordinate\/timing state before the emission of the
-- current [Gtk.GestureStylus[motion](#g:signal:motion)] signal.
-- 
-- This function may only be called within a [GestureStylus::motion]("GI.Gtk.Objects.GestureStylus#g:signal:motion")
-- signal handler, the state given in this signal and obtainable through
-- 'GI.Gtk.Objects.GestureStylus.gestureStylusGetAxis' express the latest (most up-to-date)
-- state in motion history.
-- 
-- The /@backlog@/ is provided in chronological order.
gestureStylusGetBacklog ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureStylus a) =>
    a
    -- ^ /@gesture@/: a @GtkGestureStylus@
    -> m ((Bool, [Gdk.TimeCoord.TimeCoord]))
    -- ^ __Returns:__ 'P.True' if there is a backlog to unfold in the current state.
gestureStylusGetBacklog :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureStylus a) =>
a -> m (Bool, [TimeCoord])
gestureStylusGetBacklog a
gesture = IO (Bool, [TimeCoord]) -> m (Bool, [TimeCoord])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [TimeCoord]) -> m (Bool, [TimeCoord]))
-> IO (Bool, [TimeCoord]) -> m (Bool, [TimeCoord])
forall a b. (a -> b) -> a -> b
$ do
    Ptr GestureStylus
gesture' <- a -> IO (Ptr GestureStylus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    Ptr (Ptr TimeCoord)
backlog <- IO (Ptr (Ptr TimeCoord))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Gdk.TimeCoord.TimeCoord))
    Ptr Word32
nElems <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr GestureStylus -> Ptr (Ptr TimeCoord) -> Ptr Word32 -> IO CInt
gtk_gesture_stylus_get_backlog Ptr GestureStylus
gesture' Ptr (Ptr TimeCoord)
backlog Ptr Word32
nElems
    Word32
nElems' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
nElems
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Ptr TimeCoord
backlog' <- Ptr (Ptr TimeCoord) -> IO (Ptr TimeCoord)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr TimeCoord)
backlog
    [Ptr TimeCoord]
backlog'' <- (Int -> Word32 -> Ptr TimeCoord -> IO [Ptr TimeCoord]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength Int
104 Word32
nElems') Ptr TimeCoord
backlog'
    [TimeCoord]
backlog''' <- (Ptr TimeCoord -> IO TimeCoord)
-> [Ptr TimeCoord] -> IO [TimeCoord]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr TimeCoord -> TimeCoord)
-> Ptr TimeCoord -> IO TimeCoord
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TimeCoord -> TimeCoord
Gdk.TimeCoord.TimeCoord) [Ptr TimeCoord]
backlog''
    Ptr TimeCoord -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr TimeCoord
backlog'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gesture
    Ptr (Ptr TimeCoord) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr TimeCoord)
backlog
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
nElems
    (Bool, [TimeCoord]) -> IO (Bool, [TimeCoord])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [TimeCoord]
backlog''')

#if defined(ENABLE_OVERLOADING)
data GestureStylusGetBacklogMethodInfo
instance (signature ~ (m ((Bool, [Gdk.TimeCoord.TimeCoord]))), MonadIO m, IsGestureStylus a) => O.OverloadedMethod GestureStylusGetBacklogMethodInfo a signature where
    overloadedMethod = gestureStylusGetBacklog

instance O.OverloadedMethodInfo GestureStylusGetBacklogMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus.gestureStylusGetBacklog",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#v:gestureStylusGetBacklog"
        })


#endif

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

foreign import ccall "gtk_gesture_stylus_get_device_tool" gtk_gesture_stylus_get_device_tool :: 
    Ptr GestureStylus ->                    -- gesture : TInterface (Name {namespace = "Gtk", name = "GestureStylus"})
    IO (Ptr Gdk.DeviceTool.DeviceTool)

-- | Returns the @GdkDeviceTool@ currently driving input through this gesture.
-- 
-- This function must be called from the handler of one of the
-- [GestureStylus::down]("GI.Gtk.Objects.GestureStylus#g:signal:down"), [GestureStylus::motion]("GI.Gtk.Objects.GestureStylus#g:signal:motion"),
-- [GestureStylus::up]("GI.Gtk.Objects.GestureStylus#g:signal:up") or [GestureStylus::proximity]("GI.Gtk.Objects.GestureStylus#g:signal:proximity")
-- signals.
gestureStylusGetDeviceTool ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureStylus a) =>
    a
    -- ^ /@gesture@/: a @GtkGestureStylus@
    -> m (Maybe Gdk.DeviceTool.DeviceTool)
    -- ^ __Returns:__ The current stylus tool
gestureStylusGetDeviceTool :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureStylus a) =>
a -> m (Maybe DeviceTool)
gestureStylusGetDeviceTool a
gesture = IO (Maybe DeviceTool) -> m (Maybe DeviceTool)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DeviceTool) -> m (Maybe DeviceTool))
-> IO (Maybe DeviceTool) -> m (Maybe DeviceTool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GestureStylus
gesture' <- a -> IO (Ptr GestureStylus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    Ptr DeviceTool
result <- Ptr GestureStylus -> IO (Ptr DeviceTool)
gtk_gesture_stylus_get_device_tool Ptr GestureStylus
gesture'
    Maybe DeviceTool
maybeResult <- Ptr DeviceTool
-> (Ptr DeviceTool -> IO DeviceTool) -> IO (Maybe DeviceTool)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DeviceTool
result ((Ptr DeviceTool -> IO DeviceTool) -> IO (Maybe DeviceTool))
-> (Ptr DeviceTool -> IO DeviceTool) -> IO (Maybe DeviceTool)
forall a b. (a -> b) -> a -> b
$ \Ptr DeviceTool
result' -> do
        DeviceTool
result'' <- ((ManagedPtr DeviceTool -> DeviceTool)
-> Ptr DeviceTool -> IO DeviceTool
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DeviceTool -> DeviceTool
Gdk.DeviceTool.DeviceTool) Ptr DeviceTool
result'
        DeviceTool -> IO DeviceTool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DeviceTool
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gesture
    Maybe DeviceTool -> IO (Maybe DeviceTool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeviceTool
maybeResult

#if defined(ENABLE_OVERLOADING)
data GestureStylusGetDeviceToolMethodInfo
instance (signature ~ (m (Maybe Gdk.DeviceTool.DeviceTool)), MonadIO m, IsGestureStylus a) => O.OverloadedMethod GestureStylusGetDeviceToolMethodInfo a signature where
    overloadedMethod = gestureStylusGetDeviceTool

instance O.OverloadedMethodInfo GestureStylusGetDeviceToolMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus.gestureStylusGetDeviceTool",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#v:gestureStylusGetDeviceTool"
        })


#endif

-- method GestureStylus::get_stylus_only
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "gesture"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GestureStylus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the gesture" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_gesture_stylus_get_stylus_only" gtk_gesture_stylus_get_stylus_only :: 
    Ptr GestureStylus ->                    -- gesture : TInterface (Name {namespace = "Gtk", name = "GestureStylus"})
    IO CInt

-- | Checks whether the gesture is for styluses only.
-- 
-- Stylus-only gestures will signal events exclusively from stylus
-- input devices.
-- 
-- /Since: 4.10/
gestureStylusGetStylusOnly ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureStylus a) =>
    a
    -- ^ /@gesture@/: the gesture
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the gesture is only for stylus events
gestureStylusGetStylusOnly :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureStylus a) =>
a -> m Bool
gestureStylusGetStylusOnly a
gesture = 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 GestureStylus
gesture' <- a -> IO (Ptr GestureStylus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    CInt
result <- Ptr GestureStylus -> IO CInt
gtk_gesture_stylus_get_stylus_only Ptr GestureStylus
gesture'
    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
gesture
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GestureStylusGetStylusOnlyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGestureStylus a) => O.OverloadedMethod GestureStylusGetStylusOnlyMethodInfo a signature where
    overloadedMethod = gestureStylusGetStylusOnly

instance O.OverloadedMethodInfo GestureStylusGetStylusOnlyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus.gestureStylusGetStylusOnly",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#v:gestureStylusGetStylusOnly"
        })


#endif

-- method GestureStylus::set_stylus_only
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "gesture"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GestureStylus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the gesture" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stylus_only"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether the gesture is used exclusivly for stylus events"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_gesture_stylus_set_stylus_only" gtk_gesture_stylus_set_stylus_only :: 
    Ptr GestureStylus ->                    -- gesture : TInterface (Name {namespace = "Gtk", name = "GestureStylus"})
    CInt ->                                 -- stylus_only : TBasicType TBoolean
    IO ()

-- | Sets the state of stylus-only
-- 
-- If true, the gesture will exclusivly handle events from stylus input deivces,
-- otherwise it\'ll handle events from any pointing device.
-- 
-- /Since: 4.10/
gestureStylusSetStylusOnly ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureStylus a) =>
    a
    -- ^ /@gesture@/: the gesture
    -> Bool
    -- ^ /@stylusOnly@/: whether the gesture is used exclusivly for stylus events
    -> m ()
gestureStylusSetStylusOnly :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureStylus a) =>
a -> Bool -> m ()
gestureStylusSetStylusOnly a
gesture Bool
stylusOnly = 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 GestureStylus
gesture' <- a -> IO (Ptr GestureStylus)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    let stylusOnly' :: CInt
stylusOnly' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
stylusOnly
    Ptr GestureStylus -> CInt -> IO ()
gtk_gesture_stylus_set_stylus_only Ptr GestureStylus
gesture' CInt
stylusOnly'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gesture
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GestureStylusSetStylusOnlyMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGestureStylus a) => O.OverloadedMethod GestureStylusSetStylusOnlyMethodInfo a signature where
    overloadedMethod = gestureStylusSetStylusOnly

instance O.OverloadedMethodInfo GestureStylusSetStylusOnlyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureStylus.gestureStylusSetStylusOnly",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-GestureStylus.html#v:gestureStylusSetStylusOnly"
        })


#endif