{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.GestureSingle
    ( 
    GestureSingle(..)                       ,
    IsGestureSingle                         ,
    toGestureSingle                         ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveGestureSingleMethod              ,
#endif
#if defined(ENABLE_OVERLOADING)
    GestureSingleGetButtonMethodInfo        ,
#endif
    gestureSingleGetButton                  ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleGetCurrentButtonMethodInfo ,
#endif
    gestureSingleGetCurrentButton           ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleGetCurrentSequenceMethodInfo,
#endif
    gestureSingleGetCurrentSequence         ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleGetExclusiveMethodInfo     ,
#endif
    gestureSingleGetExclusive               ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleGetTouchOnlyMethodInfo     ,
#endif
    gestureSingleGetTouchOnly               ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleSetButtonMethodInfo        ,
#endif
    gestureSingleSetButton                  ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleSetExclusiveMethodInfo     ,
#endif
    gestureSingleSetExclusive               ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleSetTouchOnlyMethodInfo     ,
#endif
    gestureSingleSetTouchOnly               ,
 
#if defined(ENABLE_OVERLOADING)
    GestureSingleButtonPropertyInfo         ,
#endif
    constructGestureSingleButton            ,
#if defined(ENABLE_OVERLOADING)
    gestureSingleButton                     ,
#endif
    getGestureSingleButton                  ,
    setGestureSingleButton                  ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleExclusivePropertyInfo      ,
#endif
    constructGestureSingleExclusive         ,
#if defined(ENABLE_OVERLOADING)
    gestureSingleExclusive                  ,
#endif
    getGestureSingleExclusive               ,
    setGestureSingleExclusive               ,
#if defined(ENABLE_OVERLOADING)
    GestureSingleTouchOnlyPropertyInfo      ,
#endif
    constructGestureSingleTouchOnly         ,
#if defined(ENABLE_OVERLOADING)
    gestureSingleTouchOnly                  ,
#endif
    getGestureSingleTouchOnly               ,
    setGestureSingleTouchOnly               ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.Gesture as Gtk.Gesture
newtype GestureSingle = GestureSingle (SP.ManagedPtr GestureSingle)
    deriving (GestureSingle -> GestureSingle -> Bool
(GestureSingle -> GestureSingle -> Bool)
-> (GestureSingle -> GestureSingle -> Bool) -> Eq GestureSingle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GestureSingle -> GestureSingle -> Bool
== :: GestureSingle -> GestureSingle -> Bool
$c/= :: GestureSingle -> GestureSingle -> Bool
/= :: GestureSingle -> GestureSingle -> Bool
Eq)
instance SP.ManagedPtrNewtype GestureSingle where
    toManagedPtr :: GestureSingle -> ManagedPtr GestureSingle
toManagedPtr (GestureSingle ManagedPtr GestureSingle
p) = ManagedPtr GestureSingle
p
foreign import ccall "gtk_gesture_single_get_type"
    c_gtk_gesture_single_get_type :: IO B.Types.GType
instance B.Types.TypedObject GestureSingle where
    glibType :: IO GType
glibType = IO GType
c_gtk_gesture_single_get_type
instance B.Types.GObject GestureSingle
class (SP.GObject o, O.IsDescendantOf GestureSingle o) => IsGestureSingle o
instance (SP.GObject o, O.IsDescendantOf GestureSingle o) => IsGestureSingle o
instance O.HasParentTypes GestureSingle
type instance O.ParentTypes GestureSingle = '[Gtk.Gesture.Gesture, Gtk.EventController.EventController, GObject.Object.Object]
toGestureSingle :: (MIO.MonadIO m, IsGestureSingle o) => o -> m GestureSingle
toGestureSingle :: forall (m :: * -> *) o.
(MonadIO m, IsGestureSingle o) =>
o -> m GestureSingle
toGestureSingle = IO GestureSingle -> m GestureSingle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO GestureSingle -> m GestureSingle)
-> (o -> IO GestureSingle) -> o -> m GestureSingle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr GestureSingle -> GestureSingle)
-> o -> IO GestureSingle
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr GestureSingle -> GestureSingle
GestureSingle
instance B.GValue.IsGValue (Maybe GestureSingle) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_gesture_single_get_type
    gvalueSet_ :: Ptr GValue -> Maybe GestureSingle -> IO ()
gvalueSet_ Ptr GValue
gv Maybe GestureSingle
P.Nothing = Ptr GValue -> Ptr GestureSingle -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr GestureSingle
forall a. Ptr a
FP.nullPtr :: FP.Ptr GestureSingle)
    gvalueSet_ Ptr GValue
gv (P.Just GestureSingle
obj) = GestureSingle -> (Ptr GestureSingle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GestureSingle
obj (Ptr GValue -> Ptr GestureSingle -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe GestureSingle)
gvalueGet_ Ptr GValue
gv = do
        Ptr GestureSingle
ptr <- Ptr GValue -> IO (Ptr GestureSingle)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr GestureSingle)
        if Ptr GestureSingle
ptr Ptr GestureSingle -> Ptr GestureSingle -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr GestureSingle
forall a. Ptr a
FP.nullPtr
        then GestureSingle -> Maybe GestureSingle
forall a. a -> Maybe a
P.Just (GestureSingle -> Maybe GestureSingle)
-> IO GestureSingle -> IO (Maybe GestureSingle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr GestureSingle -> GestureSingle)
-> Ptr GestureSingle -> IO GestureSingle
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr GestureSingle -> GestureSingle
GestureSingle Ptr GestureSingle
ptr
        else Maybe GestureSingle -> IO (Maybe GestureSingle)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GestureSingle
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveGestureSingleMethod (t :: Symbol) (o :: *) :: * where
    ResolveGestureSingleMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGestureSingleMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGestureSingleMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGestureSingleMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGestureSingleMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGestureSingleMethod "group" o = Gtk.Gesture.GestureGroupMethodInfo
    ResolveGestureSingleMethod "handlesSequence" o = Gtk.Gesture.GestureHandlesSequenceMethodInfo
    ResolveGestureSingleMethod "isActive" o = Gtk.Gesture.GestureIsActiveMethodInfo
    ResolveGestureSingleMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGestureSingleMethod "isGroupedWith" o = Gtk.Gesture.GestureIsGroupedWithMethodInfo
    ResolveGestureSingleMethod "isRecognized" o = Gtk.Gesture.GestureIsRecognizedMethodInfo
    ResolveGestureSingleMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGestureSingleMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGestureSingleMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGestureSingleMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGestureSingleMethod "reset" o = Gtk.EventController.EventControllerResetMethodInfo
    ResolveGestureSingleMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGestureSingleMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGestureSingleMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGestureSingleMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGestureSingleMethod "ungroup" o = Gtk.Gesture.GestureUngroupMethodInfo
    ResolveGestureSingleMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGestureSingleMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGestureSingleMethod "getBoundingBox" o = Gtk.Gesture.GestureGetBoundingBoxMethodInfo
    ResolveGestureSingleMethod "getBoundingBoxCenter" o = Gtk.Gesture.GestureGetBoundingBoxCenterMethodInfo
    ResolveGestureSingleMethod "getButton" o = GestureSingleGetButtonMethodInfo
    ResolveGestureSingleMethod "getCurrentButton" o = GestureSingleGetCurrentButtonMethodInfo
    ResolveGestureSingleMethod "getCurrentEvent" o = Gtk.EventController.EventControllerGetCurrentEventMethodInfo
    ResolveGestureSingleMethod "getCurrentEventDevice" o = Gtk.EventController.EventControllerGetCurrentEventDeviceMethodInfo
    ResolveGestureSingleMethod "getCurrentEventState" o = Gtk.EventController.EventControllerGetCurrentEventStateMethodInfo
    ResolveGestureSingleMethod "getCurrentEventTime" o = Gtk.EventController.EventControllerGetCurrentEventTimeMethodInfo
    ResolveGestureSingleMethod "getCurrentSequence" o = GestureSingleGetCurrentSequenceMethodInfo
    ResolveGestureSingleMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGestureSingleMethod "getDevice" o = Gtk.Gesture.GestureGetDeviceMethodInfo
    ResolveGestureSingleMethod "getExclusive" o = GestureSingleGetExclusiveMethodInfo
    ResolveGestureSingleMethod "getGroup" o = Gtk.Gesture.GestureGetGroupMethodInfo
    ResolveGestureSingleMethod "getLastEvent" o = Gtk.Gesture.GestureGetLastEventMethodInfo
    ResolveGestureSingleMethod "getLastUpdatedSequence" o = Gtk.Gesture.GestureGetLastUpdatedSequenceMethodInfo
    ResolveGestureSingleMethod "getName" o = Gtk.EventController.EventControllerGetNameMethodInfo
    ResolveGestureSingleMethod "getPoint" o = Gtk.Gesture.GestureGetPointMethodInfo
    ResolveGestureSingleMethod "getPropagationLimit" o = Gtk.EventController.EventControllerGetPropagationLimitMethodInfo
    ResolveGestureSingleMethod "getPropagationPhase" o = Gtk.EventController.EventControllerGetPropagationPhaseMethodInfo
    ResolveGestureSingleMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGestureSingleMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGestureSingleMethod "getSequenceState" o = Gtk.Gesture.GestureGetSequenceStateMethodInfo
    ResolveGestureSingleMethod "getSequences" o = Gtk.Gesture.GestureGetSequencesMethodInfo
    ResolveGestureSingleMethod "getTouchOnly" o = GestureSingleGetTouchOnlyMethodInfo
    ResolveGestureSingleMethod "getWidget" o = Gtk.EventController.EventControllerGetWidgetMethodInfo
    ResolveGestureSingleMethod "setButton" o = GestureSingleSetButtonMethodInfo
    ResolveGestureSingleMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGestureSingleMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGestureSingleMethod "setExclusive" o = GestureSingleSetExclusiveMethodInfo
    ResolveGestureSingleMethod "setName" o = Gtk.EventController.EventControllerSetNameMethodInfo
    ResolveGestureSingleMethod "setPropagationLimit" o = Gtk.EventController.EventControllerSetPropagationLimitMethodInfo
    ResolveGestureSingleMethod "setPropagationPhase" o = Gtk.EventController.EventControllerSetPropagationPhaseMethodInfo
    ResolveGestureSingleMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGestureSingleMethod "setSequenceState" o = Gtk.Gesture.GestureSetSequenceStateMethodInfo
    ResolveGestureSingleMethod "setState" o = Gtk.Gesture.GestureSetStateMethodInfo
    ResolveGestureSingleMethod "setStaticName" o = Gtk.EventController.EventControllerSetStaticNameMethodInfo
    ResolveGestureSingleMethod "setTouchOnly" o = GestureSingleSetTouchOnlyMethodInfo
    ResolveGestureSingleMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveGestureSingleMethod t GestureSingle, O.OverloadedMethod info GestureSingle p) => OL.IsLabel t (GestureSingle -> 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 ~ ResolveGestureSingleMethod t GestureSingle, O.OverloadedMethod info GestureSingle p, R.HasField t GestureSingle p) => R.HasField t GestureSingle p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveGestureSingleMethod t GestureSingle, O.OverloadedMethodInfo info GestureSingle) => OL.IsLabel t (O.MethodProxy info GestureSingle) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
   
   
   
getGestureSingleButton :: (MonadIO m, IsGestureSingle o) => o -> m Word32
getGestureSingleButton :: forall (m :: * -> *) o.
(MonadIO m, IsGestureSingle o) =>
o -> m Word32
getGestureSingleButton o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"button"
setGestureSingleButton :: (MonadIO m, IsGestureSingle o) => o -> Word32 -> m ()
setGestureSingleButton :: forall (m :: * -> *) o.
(MonadIO m, IsGestureSingle o) =>
o -> Word32 -> m ()
setGestureSingleButton o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"button" Word32
val
constructGestureSingleButton :: (IsGestureSingle o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructGestureSingleButton :: forall o (m :: * -> *).
(IsGestureSingle o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructGestureSingleButton Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"button" Word32
val
#if defined(ENABLE_OVERLOADING)
data GestureSingleButtonPropertyInfo
instance AttrInfo GestureSingleButtonPropertyInfo where
    type AttrAllowedOps GestureSingleButtonPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GestureSingleButtonPropertyInfo = IsGestureSingle
    type AttrSetTypeConstraint GestureSingleButtonPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint GestureSingleButtonPropertyInfo = (~) Word32
    type AttrTransferType GestureSingleButtonPropertyInfo = Word32
    type AttrGetType GestureSingleButtonPropertyInfo = Word32
    type AttrLabel GestureSingleButtonPropertyInfo = "button"
    type AttrOrigin GestureSingleButtonPropertyInfo = GestureSingle
    attrGet = getGestureSingleButton
    attrSet = setGestureSingleButton
    attrTransfer _ v = do
        return v
    attrConstruct = constructGestureSingleButton
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.button"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#g:attr:button"
        })
#endif
   
   
   
getGestureSingleExclusive :: (MonadIO m, IsGestureSingle o) => o -> m Bool
getGestureSingleExclusive :: forall (m :: * -> *) o.
(MonadIO m, IsGestureSingle o) =>
o -> m Bool
getGestureSingleExclusive 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
"exclusive"
setGestureSingleExclusive :: (MonadIO m, IsGestureSingle o) => o -> Bool -> m ()
setGestureSingleExclusive :: forall (m :: * -> *) o.
(MonadIO m, IsGestureSingle o) =>
o -> Bool -> m ()
setGestureSingleExclusive 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
"exclusive" Bool
val
constructGestureSingleExclusive :: (IsGestureSingle o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructGestureSingleExclusive :: forall o (m :: * -> *).
(IsGestureSingle o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructGestureSingleExclusive 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
"exclusive" Bool
val
#if defined(ENABLE_OVERLOADING)
data GestureSingleExclusivePropertyInfo
instance AttrInfo GestureSingleExclusivePropertyInfo where
    type AttrAllowedOps GestureSingleExclusivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GestureSingleExclusivePropertyInfo = IsGestureSingle
    type AttrSetTypeConstraint GestureSingleExclusivePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint GestureSingleExclusivePropertyInfo = (~) Bool
    type AttrTransferType GestureSingleExclusivePropertyInfo = Bool
    type AttrGetType GestureSingleExclusivePropertyInfo = Bool
    type AttrLabel GestureSingleExclusivePropertyInfo = "exclusive"
    type AttrOrigin GestureSingleExclusivePropertyInfo = GestureSingle
    attrGet = getGestureSingleExclusive
    attrSet = setGestureSingleExclusive
    attrTransfer _ v = do
        return v
    attrConstruct = constructGestureSingleExclusive
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.exclusive"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#g:attr:exclusive"
        })
#endif
   
   
   
getGestureSingleTouchOnly :: (MonadIO m, IsGestureSingle o) => o -> m Bool
getGestureSingleTouchOnly :: forall (m :: * -> *) o.
(MonadIO m, IsGestureSingle o) =>
o -> m Bool
getGestureSingleTouchOnly 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
"touch-only"
setGestureSingleTouchOnly :: (MonadIO m, IsGestureSingle o) => o -> Bool -> m ()
setGestureSingleTouchOnly :: forall (m :: * -> *) o.
(MonadIO m, IsGestureSingle o) =>
o -> Bool -> m ()
setGestureSingleTouchOnly 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
"touch-only" Bool
val
constructGestureSingleTouchOnly :: (IsGestureSingle o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructGestureSingleTouchOnly :: forall o (m :: * -> *).
(IsGestureSingle o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructGestureSingleTouchOnly 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
"touch-only" Bool
val
#if defined(ENABLE_OVERLOADING)
data GestureSingleTouchOnlyPropertyInfo
instance AttrInfo GestureSingleTouchOnlyPropertyInfo where
    type AttrAllowedOps GestureSingleTouchOnlyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GestureSingleTouchOnlyPropertyInfo = IsGestureSingle
    type AttrSetTypeConstraint GestureSingleTouchOnlyPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint GestureSingleTouchOnlyPropertyInfo = (~) Bool
    type AttrTransferType GestureSingleTouchOnlyPropertyInfo = Bool
    type AttrGetType GestureSingleTouchOnlyPropertyInfo = Bool
    type AttrLabel GestureSingleTouchOnlyPropertyInfo = "touch-only"
    type AttrOrigin GestureSingleTouchOnlyPropertyInfo = GestureSingle
    attrGet = getGestureSingleTouchOnly
    attrSet = setGestureSingleTouchOnly
    attrTransfer _ v = do
        return v
    attrConstruct = constructGestureSingleTouchOnly
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.touchOnly"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#g:attr:touchOnly"
        })
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GestureSingle
type instance O.AttributeList GestureSingle = GestureSingleAttributeList
type GestureSingleAttributeList = ('[ '("button", GestureSingleButtonPropertyInfo), '("exclusive", GestureSingleExclusivePropertyInfo), '("nPoints", Gtk.Gesture.GestureNPointsPropertyInfo), '("name", Gtk.EventController.EventControllerNamePropertyInfo), '("propagationLimit", Gtk.EventController.EventControllerPropagationLimitPropertyInfo), '("propagationPhase", Gtk.EventController.EventControllerPropagationPhasePropertyInfo), '("touchOnly", GestureSingleTouchOnlyPropertyInfo), '("widget", Gtk.EventController.EventControllerWidgetPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
gestureSingleButton :: AttrLabelProxy "button"
gestureSingleButton = AttrLabelProxy
gestureSingleExclusive :: AttrLabelProxy "exclusive"
gestureSingleExclusive = AttrLabelProxy
gestureSingleTouchOnly :: AttrLabelProxy "touchOnly"
gestureSingleTouchOnly = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GestureSingle = GestureSingleSignalList
type GestureSingleSignalList = ('[ '("begin", Gtk.Gesture.GestureBeginSignalInfo), '("cancel", Gtk.Gesture.GestureCancelSignalInfo), '("end", Gtk.Gesture.GestureEndSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("sequenceStateChanged", Gtk.Gesture.GestureSequenceStateChangedSignalInfo), '("update", Gtk.Gesture.GestureUpdateSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_gesture_single_get_button" gtk_gesture_single_get_button :: 
    Ptr GestureSingle ->                    
    IO Word32
gestureSingleGetButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureSingle a) =>
    a
    
    -> m Word32
    
gestureSingleGetButton :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureSingle a) =>
a -> m Word32
gestureSingleGetButton a
gesture = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GestureSingle
gesture' <- a -> IO (Ptr GestureSingle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    Word32
result <- Ptr GestureSingle -> IO Word32
gtk_gesture_single_get_button Ptr GestureSingle
gesture'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gesture
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data GestureSingleGetButtonMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsGestureSingle a) => O.OverloadedMethod GestureSingleGetButtonMethodInfo a signature where
    overloadedMethod = gestureSingleGetButton
instance O.OverloadedMethodInfo GestureSingleGetButtonMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.gestureSingleGetButton",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#v:gestureSingleGetButton"
        })
#endif
foreign import ccall "gtk_gesture_single_get_current_button" gtk_gesture_single_get_current_button :: 
    Ptr GestureSingle ->                    
    IO Word32
gestureSingleGetCurrentButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureSingle a) =>
    a
    
    -> m Word32
    
gestureSingleGetCurrentButton :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureSingle a) =>
a -> m Word32
gestureSingleGetCurrentButton a
gesture = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GestureSingle
gesture' <- a -> IO (Ptr GestureSingle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    Word32
result <- Ptr GestureSingle -> IO Word32
gtk_gesture_single_get_current_button Ptr GestureSingle
gesture'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gesture
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data GestureSingleGetCurrentButtonMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsGestureSingle a) => O.OverloadedMethod GestureSingleGetCurrentButtonMethodInfo a signature where
    overloadedMethod = gestureSingleGetCurrentButton
instance O.OverloadedMethodInfo GestureSingleGetCurrentButtonMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.gestureSingleGetCurrentButton",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#v:gestureSingleGetCurrentButton"
        })
#endif
foreign import ccall "gtk_gesture_single_get_current_sequence" gtk_gesture_single_get_current_sequence :: 
    Ptr GestureSingle ->                    
    IO (Ptr Gdk.EventSequence.EventSequence)
gestureSingleGetCurrentSequence ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureSingle a) =>
    a
    
    -> m (Maybe Gdk.EventSequence.EventSequence)
    
gestureSingleGetCurrentSequence :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureSingle a) =>
a -> m (Maybe EventSequence)
gestureSingleGetCurrentSequence a
gesture = IO (Maybe EventSequence) -> m (Maybe EventSequence)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe EventSequence) -> m (Maybe EventSequence))
-> IO (Maybe EventSequence) -> m (Maybe EventSequence)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GestureSingle
gesture' <- a -> IO (Ptr GestureSingle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    Ptr EventSequence
result <- Ptr GestureSingle -> IO (Ptr EventSequence)
gtk_gesture_single_get_current_sequence Ptr GestureSingle
gesture'
    Maybe EventSequence
maybeResult <- Ptr EventSequence
-> (Ptr EventSequence -> IO EventSequence)
-> IO (Maybe EventSequence)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr EventSequence
result ((Ptr EventSequence -> IO EventSequence)
 -> IO (Maybe EventSequence))
-> (Ptr EventSequence -> IO EventSequence)
-> IO (Maybe EventSequence)
forall a b. (a -> b) -> a -> b
$ \Ptr EventSequence
result' -> do
        EventSequence
result'' <- ((ManagedPtr EventSequence -> EventSequence)
-> Ptr EventSequence -> IO EventSequence
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr EventSequence -> EventSequence
Gdk.EventSequence.EventSequence) Ptr EventSequence
result'
        EventSequence -> IO EventSequence
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EventSequence
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gesture
    Maybe EventSequence -> IO (Maybe EventSequence)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EventSequence
maybeResult
#if defined(ENABLE_OVERLOADING)
data GestureSingleGetCurrentSequenceMethodInfo
instance (signature ~ (m (Maybe Gdk.EventSequence.EventSequence)), MonadIO m, IsGestureSingle a) => O.OverloadedMethod GestureSingleGetCurrentSequenceMethodInfo a signature where
    overloadedMethod = gestureSingleGetCurrentSequence
instance O.OverloadedMethodInfo GestureSingleGetCurrentSequenceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.gestureSingleGetCurrentSequence",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#v:gestureSingleGetCurrentSequence"
        })
#endif
foreign import ccall "gtk_gesture_single_get_exclusive" gtk_gesture_single_get_exclusive :: 
    Ptr GestureSingle ->                    
    IO CInt
gestureSingleGetExclusive ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureSingle a) =>
    a
    
    -> m Bool
    
gestureSingleGetExclusive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureSingle a) =>
a -> m Bool
gestureSingleGetExclusive 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 GestureSingle
gesture' <- a -> IO (Ptr GestureSingle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    CInt
result <- Ptr GestureSingle -> IO CInt
gtk_gesture_single_get_exclusive Ptr GestureSingle
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 GestureSingleGetExclusiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGestureSingle a) => O.OverloadedMethod GestureSingleGetExclusiveMethodInfo a signature where
    overloadedMethod = gestureSingleGetExclusive
instance O.OverloadedMethodInfo GestureSingleGetExclusiveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.gestureSingleGetExclusive",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#v:gestureSingleGetExclusive"
        })
#endif
foreign import ccall "gtk_gesture_single_get_touch_only" gtk_gesture_single_get_touch_only :: 
    Ptr GestureSingle ->                    
    IO CInt
gestureSingleGetTouchOnly ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureSingle a) =>
    a
    
    -> m Bool
    
gestureSingleGetTouchOnly :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureSingle a) =>
a -> m Bool
gestureSingleGetTouchOnly 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 GestureSingle
gesture' <- a -> IO (Ptr GestureSingle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    CInt
result <- Ptr GestureSingle -> IO CInt
gtk_gesture_single_get_touch_only Ptr GestureSingle
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 GestureSingleGetTouchOnlyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGestureSingle a) => O.OverloadedMethod GestureSingleGetTouchOnlyMethodInfo a signature where
    overloadedMethod = gestureSingleGetTouchOnly
instance O.OverloadedMethodInfo GestureSingleGetTouchOnlyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.gestureSingleGetTouchOnly",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#v:gestureSingleGetTouchOnly"
        })
#endif
foreign import ccall "gtk_gesture_single_set_button" gtk_gesture_single_set_button :: 
    Ptr GestureSingle ->                    
    Word32 ->                               
    IO ()
gestureSingleSetButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureSingle a) =>
    a
    
    -> Word32
    
    -> m ()
gestureSingleSetButton :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureSingle a) =>
a -> Word32 -> m ()
gestureSingleSetButton a
gesture Word32
button = 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 GestureSingle
gesture' <- a -> IO (Ptr GestureSingle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    Ptr GestureSingle -> Word32 -> IO ()
gtk_gesture_single_set_button Ptr GestureSingle
gesture' Word32
button
    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 GestureSingleSetButtonMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsGestureSingle a) => O.OverloadedMethod GestureSingleSetButtonMethodInfo a signature where
    overloadedMethod = gestureSingleSetButton
instance O.OverloadedMethodInfo GestureSingleSetButtonMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.gestureSingleSetButton",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#v:gestureSingleSetButton"
        })
#endif
foreign import ccall "gtk_gesture_single_set_exclusive" gtk_gesture_single_set_exclusive :: 
    Ptr GestureSingle ->                    
    CInt ->                                 
    IO ()
gestureSingleSetExclusive ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureSingle a) =>
    a
    
    -> Bool
    
    -> m ()
gestureSingleSetExclusive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureSingle a) =>
a -> Bool -> m ()
gestureSingleSetExclusive a
gesture Bool
exclusive = 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 GestureSingle
gesture' <- a -> IO (Ptr GestureSingle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    let exclusive' :: CInt
exclusive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
exclusive
    Ptr GestureSingle -> CInt -> IO ()
gtk_gesture_single_set_exclusive Ptr GestureSingle
gesture' CInt
exclusive'
    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 GestureSingleSetExclusiveMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGestureSingle a) => O.OverloadedMethod GestureSingleSetExclusiveMethodInfo a signature where
    overloadedMethod = gestureSingleSetExclusive
instance O.OverloadedMethodInfo GestureSingleSetExclusiveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.gestureSingleSetExclusive",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#v:gestureSingleSetExclusive"
        })
#endif
foreign import ccall "gtk_gesture_single_set_touch_only" gtk_gesture_single_set_touch_only :: 
    Ptr GestureSingle ->                    
    CInt ->                                 
    IO ()
gestureSingleSetTouchOnly ::
    (B.CallStack.HasCallStack, MonadIO m, IsGestureSingle a) =>
    a
    
    -> Bool
    
    -> m ()
gestureSingleSetTouchOnly :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGestureSingle a) =>
a -> Bool -> m ()
gestureSingleSetTouchOnly a
gesture Bool
touchOnly = 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 GestureSingle
gesture' <- a -> IO (Ptr GestureSingle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gesture
    let touchOnly' :: CInt
touchOnly' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
touchOnly
    Ptr GestureSingle -> CInt -> IO ()
gtk_gesture_single_set_touch_only Ptr GestureSingle
gesture' CInt
touchOnly'
    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 GestureSingleSetTouchOnlyMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGestureSingle a) => O.OverloadedMethod GestureSingleSetTouchOnlyMethodInfo a signature where
    overloadedMethod = gestureSingleSetTouchOnly
instance O.OverloadedMethodInfo GestureSingleSetTouchOnlyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GestureSingle.gestureSingleSetTouchOnly",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-GestureSingle.html#v:gestureSingleSetTouchOnly"
        })
#endif