{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Interfaces.DevicePad
(
DevicePad(..) ,
IsDevicePad ,
toDevicePad ,
#if defined(ENABLE_OVERLOADING)
ResolveDevicePadMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DevicePadGetFeatureGroupMethodInfo ,
#endif
devicePadGetFeatureGroup ,
#if defined(ENABLE_OVERLOADING)
DevicePadGetGroupNModesMethodInfo ,
#endif
devicePadGetGroupNModes ,
#if defined(ENABLE_OVERLOADING)
DevicePadGetNFeaturesMethodInfo ,
#endif
devicePadGetNFeatures ,
#if defined(ENABLE_OVERLOADING)
DevicePadGetNGroupsMethodInfo ,
#endif
devicePadGetNGroups ,
) 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 {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
newtype DevicePad = DevicePad (SP.ManagedPtr DevicePad)
deriving (DevicePad -> DevicePad -> Bool
(DevicePad -> DevicePad -> Bool)
-> (DevicePad -> DevicePad -> Bool) -> Eq DevicePad
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DevicePad -> DevicePad -> Bool
== :: DevicePad -> DevicePad -> Bool
$c/= :: DevicePad -> DevicePad -> Bool
/= :: DevicePad -> DevicePad -> Bool
Eq)
instance SP.ManagedPtrNewtype DevicePad where
toManagedPtr :: DevicePad -> ManagedPtr DevicePad
toManagedPtr (DevicePad ManagedPtr DevicePad
p) = ManagedPtr DevicePad
p
foreign import ccall "gdk_device_pad_get_type"
c_gdk_device_pad_get_type :: IO B.Types.GType
instance B.Types.TypedObject DevicePad where
glibType :: IO GType
glibType = IO GType
c_gdk_device_pad_get_type
instance B.Types.GObject DevicePad
class (SP.GObject o, O.IsDescendantOf DevicePad o) => IsDevicePad o
instance (SP.GObject o, O.IsDescendantOf DevicePad o) => IsDevicePad o
instance O.HasParentTypes DevicePad
type instance O.ParentTypes DevicePad = '[Gdk.Device.Device, GObject.Object.Object]
toDevicePad :: (MIO.MonadIO m, IsDevicePad o) => o -> m DevicePad
toDevicePad :: forall (m :: * -> *) o.
(MonadIO m, IsDevicePad o) =>
o -> m DevicePad
toDevicePad = IO DevicePad -> m DevicePad
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DevicePad -> m DevicePad)
-> (o -> IO DevicePad) -> o -> m DevicePad
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DevicePad -> DevicePad) -> o -> IO DevicePad
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DevicePad -> DevicePad
DevicePad
instance B.GValue.IsGValue (Maybe DevicePad) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_device_pad_get_type
gvalueSet_ :: Ptr GValue -> Maybe DevicePad -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DevicePad
P.Nothing = Ptr GValue -> Ptr DevicePad -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DevicePad
forall a. Ptr a
FP.nullPtr :: FP.Ptr DevicePad)
gvalueSet_ Ptr GValue
gv (P.Just DevicePad
obj) = DevicePad -> (Ptr DevicePad -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DevicePad
obj (Ptr GValue -> Ptr DevicePad -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DevicePad)
gvalueGet_ Ptr GValue
gv = do
Ptr DevicePad
ptr <- Ptr GValue -> IO (Ptr DevicePad)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DevicePad)
if Ptr DevicePad
ptr Ptr DevicePad -> Ptr DevicePad -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DevicePad
forall a. Ptr a
FP.nullPtr
then DevicePad -> Maybe DevicePad
forall a. a -> Maybe a
P.Just (DevicePad -> Maybe DevicePad)
-> IO DevicePad -> IO (Maybe DevicePad)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DevicePad -> DevicePad)
-> Ptr DevicePad -> IO DevicePad
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DevicePad -> DevicePad
DevicePad Ptr DevicePad
ptr
else Maybe DevicePad -> IO (Maybe DevicePad)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DevicePad
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DevicePad
type instance O.AttributeList DevicePad = DevicePadAttributeList
type DevicePadAttributeList = ('[ '("associatedDevice", Gdk.Device.DeviceAssociatedDevicePropertyInfo), '("axes", Gdk.Device.DeviceAxesPropertyInfo), '("deviceManager", Gdk.Device.DeviceDeviceManagerPropertyInfo), '("display", Gdk.Device.DeviceDisplayPropertyInfo), '("hasCursor", Gdk.Device.DeviceHasCursorPropertyInfo), '("inputMode", Gdk.Device.DeviceInputModePropertyInfo), '("inputSource", Gdk.Device.DeviceInputSourcePropertyInfo), '("nAxes", Gdk.Device.DeviceNAxesPropertyInfo), '("name", Gdk.Device.DeviceNamePropertyInfo), '("numTouches", Gdk.Device.DeviceNumTouchesPropertyInfo), '("productId", Gdk.Device.DeviceProductIdPropertyInfo), '("seat", Gdk.Device.DeviceSeatPropertyInfo), '("tool", Gdk.Device.DeviceToolPropertyInfo), '("type", Gdk.Device.DeviceTypePropertyInfo), '("vendorId", Gdk.Device.DeviceVendorIdPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveDevicePadMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDevicePadMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDevicePadMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDevicePadMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDevicePadMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDevicePadMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDevicePadMethod "grab" o = Gdk.Device.DeviceGrabMethodInfo
ResolveDevicePadMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDevicePadMethod "listAxes" o = Gdk.Device.DeviceListAxesMethodInfo
ResolveDevicePadMethod "listSlaveDevices" o = Gdk.Device.DeviceListSlaveDevicesMethodInfo
ResolveDevicePadMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDevicePadMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDevicePadMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDevicePadMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDevicePadMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDevicePadMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDevicePadMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDevicePadMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDevicePadMethod "ungrab" o = Gdk.Device.DeviceUngrabMethodInfo
ResolveDevicePadMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDevicePadMethod "warp" o = Gdk.Device.DeviceWarpMethodInfo
ResolveDevicePadMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDevicePadMethod "getAssociatedDevice" o = Gdk.Device.DeviceGetAssociatedDeviceMethodInfo
ResolveDevicePadMethod "getAxes" o = Gdk.Device.DeviceGetAxesMethodInfo
ResolveDevicePadMethod "getAxisUse" o = Gdk.Device.DeviceGetAxisUseMethodInfo
ResolveDevicePadMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDevicePadMethod "getDeviceType" o = Gdk.Device.DeviceGetDeviceTypeMethodInfo
ResolveDevicePadMethod "getDisplay" o = Gdk.Device.DeviceGetDisplayMethodInfo
ResolveDevicePadMethod "getFeatureGroup" o = DevicePadGetFeatureGroupMethodInfo
ResolveDevicePadMethod "getGroupNModes" o = DevicePadGetGroupNModesMethodInfo
ResolveDevicePadMethod "getHasCursor" o = Gdk.Device.DeviceGetHasCursorMethodInfo
ResolveDevicePadMethod "getKey" o = Gdk.Device.DeviceGetKeyMethodInfo
ResolveDevicePadMethod "getLastEventWindow" o = Gdk.Device.DeviceGetLastEventWindowMethodInfo
ResolveDevicePadMethod "getMode" o = Gdk.Device.DeviceGetModeMethodInfo
ResolveDevicePadMethod "getNAxes" o = Gdk.Device.DeviceGetNAxesMethodInfo
ResolveDevicePadMethod "getNFeatures" o = DevicePadGetNFeaturesMethodInfo
ResolveDevicePadMethod "getNGroups" o = DevicePadGetNGroupsMethodInfo
ResolveDevicePadMethod "getNKeys" o = Gdk.Device.DeviceGetNKeysMethodInfo
ResolveDevicePadMethod "getName" o = Gdk.Device.DeviceGetNameMethodInfo
ResolveDevicePadMethod "getPosition" o = Gdk.Device.DeviceGetPositionMethodInfo
ResolveDevicePadMethod "getPositionDouble" o = Gdk.Device.DeviceGetPositionDoubleMethodInfo
ResolveDevicePadMethod "getProductId" o = Gdk.Device.DeviceGetProductIdMethodInfo
ResolveDevicePadMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDevicePadMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDevicePadMethod "getSeat" o = Gdk.Device.DeviceGetSeatMethodInfo
ResolveDevicePadMethod "getSource" o = Gdk.Device.DeviceGetSourceMethodInfo
ResolveDevicePadMethod "getVendorId" o = Gdk.Device.DeviceGetVendorIdMethodInfo
ResolveDevicePadMethod "getWindowAtPosition" o = Gdk.Device.DeviceGetWindowAtPositionMethodInfo
ResolveDevicePadMethod "getWindowAtPositionDouble" o = Gdk.Device.DeviceGetWindowAtPositionDoubleMethodInfo
ResolveDevicePadMethod "setAxisUse" o = Gdk.Device.DeviceSetAxisUseMethodInfo
ResolveDevicePadMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDevicePadMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDevicePadMethod "setKey" o = Gdk.Device.DeviceSetKeyMethodInfo
ResolveDevicePadMethod "setMode" o = Gdk.Device.DeviceSetModeMethodInfo
ResolveDevicePadMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDevicePadMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDevicePadMethod t DevicePad, O.OverloadedMethod info DevicePad p) => OL.IsLabel t (DevicePad -> 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 ~ ResolveDevicePadMethod t DevicePad, O.OverloadedMethod info DevicePad p, R.HasField t DevicePad p) => R.HasField t DevicePad p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDevicePadMethod t DevicePad, O.OverloadedMethodInfo info DevicePad) => OL.IsLabel t (O.MethodProxy info DevicePad) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "gdk_device_pad_get_feature_group" gdk_device_pad_get_feature_group ::
Ptr DevicePad ->
CUInt ->
Int32 ->
IO Int32
devicePadGetFeatureGroup ::
(B.CallStack.HasCallStack, MonadIO m, IsDevicePad a) =>
a
-> Gdk.Enums.DevicePadFeature
-> Int32
-> m Int32
devicePadGetFeatureGroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevicePad a) =>
a -> DevicePadFeature -> Int32 -> m Int32
devicePadGetFeatureGroup a
pad DevicePadFeature
feature Int32
featureIdx = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr DevicePad
pad' <- a -> IO (Ptr DevicePad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pad
let feature' :: CUInt
feature' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (DevicePadFeature -> Int) -> DevicePadFeature -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DevicePadFeature -> Int
forall a. Enum a => a -> Int
fromEnum) DevicePadFeature
feature
Int32
result <- Ptr DevicePad -> CUInt -> Int32 -> IO Int32
gdk_device_pad_get_feature_group Ptr DevicePad
pad' CUInt
feature' Int32
featureIdx
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pad
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DevicePadGetFeatureGroupMethodInfo
instance (signature ~ (Gdk.Enums.DevicePadFeature -> Int32 -> m Int32), MonadIO m, IsDevicePad a) => O.OverloadedMethod DevicePadGetFeatureGroupMethodInfo a signature where
overloadedMethod = devicePadGetFeatureGroup
instance O.OverloadedMethodInfo DevicePadGetFeatureGroupMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Interfaces.DevicePad.devicePadGetFeatureGroup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.28/docs/GI-Gdk-Interfaces-DevicePad.html#v:devicePadGetFeatureGroup"
})
#endif
foreign import ccall "gdk_device_pad_get_group_n_modes" gdk_device_pad_get_group_n_modes ::
Ptr DevicePad ->
Int32 ->
IO Int32
devicePadGetGroupNModes ::
(B.CallStack.HasCallStack, MonadIO m, IsDevicePad a) =>
a
-> Int32
-> m Int32
devicePadGetGroupNModes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevicePad a) =>
a -> Int32 -> m Int32
devicePadGetGroupNModes a
pad Int32
groupIdx = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr DevicePad
pad' <- a -> IO (Ptr DevicePad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pad
Int32
result <- Ptr DevicePad -> Int32 -> IO Int32
gdk_device_pad_get_group_n_modes Ptr DevicePad
pad' Int32
groupIdx
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pad
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DevicePadGetGroupNModesMethodInfo
instance (signature ~ (Int32 -> m Int32), MonadIO m, IsDevicePad a) => O.OverloadedMethod DevicePadGetGroupNModesMethodInfo a signature where
overloadedMethod = devicePadGetGroupNModes
instance O.OverloadedMethodInfo DevicePadGetGroupNModesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Interfaces.DevicePad.devicePadGetGroupNModes",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.28/docs/GI-Gdk-Interfaces-DevicePad.html#v:devicePadGetGroupNModes"
})
#endif
foreign import ccall "gdk_device_pad_get_n_features" gdk_device_pad_get_n_features ::
Ptr DevicePad ->
CUInt ->
IO Int32
devicePadGetNFeatures ::
(B.CallStack.HasCallStack, MonadIO m, IsDevicePad a) =>
a
-> Gdk.Enums.DevicePadFeature
-> m Int32
devicePadGetNFeatures :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevicePad a) =>
a -> DevicePadFeature -> m Int32
devicePadGetNFeatures a
pad DevicePadFeature
feature = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr DevicePad
pad' <- a -> IO (Ptr DevicePad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pad
let feature' :: CUInt
feature' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (DevicePadFeature -> Int) -> DevicePadFeature -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DevicePadFeature -> Int
forall a. Enum a => a -> Int
fromEnum) DevicePadFeature
feature
Int32
result <- Ptr DevicePad -> CUInt -> IO Int32
gdk_device_pad_get_n_features Ptr DevicePad
pad' CUInt
feature'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pad
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DevicePadGetNFeaturesMethodInfo
instance (signature ~ (Gdk.Enums.DevicePadFeature -> m Int32), MonadIO m, IsDevicePad a) => O.OverloadedMethod DevicePadGetNFeaturesMethodInfo a signature where
overloadedMethod = devicePadGetNFeatures
instance O.OverloadedMethodInfo DevicePadGetNFeaturesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Interfaces.DevicePad.devicePadGetNFeatures",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.28/docs/GI-Gdk-Interfaces-DevicePad.html#v:devicePadGetNFeatures"
})
#endif
foreign import ccall "gdk_device_pad_get_n_groups" gdk_device_pad_get_n_groups ::
Ptr DevicePad ->
IO Int32
devicePadGetNGroups ::
(B.CallStack.HasCallStack, MonadIO m, IsDevicePad a) =>
a
-> m Int32
devicePadGetNGroups :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevicePad a) =>
a -> m Int32
devicePadGetNGroups a
pad = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr DevicePad
pad' <- a -> IO (Ptr DevicePad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pad
Int32
result <- Ptr DevicePad -> IO Int32
gdk_device_pad_get_n_groups Ptr DevicePad
pad'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pad
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DevicePadGetNGroupsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDevicePad a) => O.OverloadedMethod DevicePadGetNGroupsMethodInfo a signature where
overloadedMethod = devicePadGetNGroups
instance O.OverloadedMethodInfo DevicePadGetNGroupsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Interfaces.DevicePad.devicePadGetNGroups",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.28/docs/GI-Gdk-Interfaces-DevicePad.html#v:devicePadGetNGroups"
})
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DevicePad = DevicePadSignalList
type DevicePadSignalList = ('[ '("changed", Gdk.Device.DeviceChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("toolChanged", Gdk.Device.DeviceToolChangedSignalInfo)] :: [(Symbol, DK.Type)])
#endif