{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gdk.Interfaces.DevicePad.DevicePad' is an interface implemented by devices of type
-- 'GI.Gdk.Enums.InputSourceTabletPad', it allows querying the features provided
-- by the pad device.
-- 
-- Tablet pads may contain one or more groups, each containing a subset
-- of the buttons\/rings\/strips available. 'GI.Gdk.Interfaces.DevicePad.devicePadGetNGroups'
-- can be used to obtain the number of groups, 'GI.Gdk.Interfaces.DevicePad.devicePadGetNFeatures'
-- and 'GI.Gdk.Interfaces.DevicePad.devicePadGetFeatureGroup' can be combined to find out the
-- number of buttons\/rings\/strips the device has, and how are they grouped.
-- 
-- Each of those groups have different modes, which may be used to map each
-- individual pad feature to multiple actions. Only one mode is effective
-- (current) for each given group, different groups may have different
-- current modes. The number of available modes in a group can be found
-- out through 'GI.Gdk.Interfaces.DevicePad.devicePadGetGroupNModes', and the current mode for
-- a given group will be notified through events of type @/GDK_PAD_GROUP_MODE/@.

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

module GI.Gdk.Interfaces.DevicePad
    ( 

-- * Exported types
    DevicePad(..)                           ,
    IsDevicePad                             ,
    toDevicePad                             ,


 -- * 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"), [hasBidiLayouts]("GI.Gdk.Objects.Device#g:method:hasBidiLayouts"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [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"), [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"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCapsLockState]("GI.Gdk.Objects.Device#g:method:getCapsLockState"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDeviceTool]("GI.Gdk.Objects.Device#g:method:getDeviceTool"), [getDirection]("GI.Gdk.Objects.Device#g:method:getDirection"), [getDisplay]("GI.Gdk.Objects.Device#g:method:getDisplay"), [getFeatureGroup]("GI.Gdk.Interfaces.DevicePad#g:method:getFeatureGroup"), [getGroupNModes]("GI.Gdk.Interfaces.DevicePad#g:method:getGroupNModes"), [getHasCursor]("GI.Gdk.Objects.Device#g:method:getHasCursor"), [getModifierState]("GI.Gdk.Objects.Device#g:method:getModifierState"), [getNFeatures]("GI.Gdk.Interfaces.DevicePad#g:method:getNFeatures"), [getNGroups]("GI.Gdk.Interfaces.DevicePad#g:method:getNGroups"), [getName]("GI.Gdk.Objects.Device#g:method:getName"), [getNumLockState]("GI.Gdk.Objects.Device#g:method:getNumLockState"), [getNumTouches]("GI.Gdk.Objects.Device#g:method:getNumTouches"), [getProductId]("GI.Gdk.Objects.Device#g:method:getProductId"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getScrollLockState]("GI.Gdk.Objects.Device#g:method:getScrollLockState"), [getSeat]("GI.Gdk.Objects.Device#g:method:getSeat"), [getSource]("GI.Gdk.Objects.Device#g:method:getSource"), [getSurfaceAtPosition]("GI.Gdk.Objects.Device#g:method:getSurfaceAtPosition"), [getVendorId]("GI.Gdk.Objects.Device#g:method:getVendorId").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDevicePadMethod                  ,
#endif

-- ** getFeatureGroup #method:getFeatureGroup#

#if defined(ENABLE_OVERLOADING)
    DevicePadGetFeatureGroupMethodInfo      ,
#endif
    devicePadGetFeatureGroup                ,


-- ** getGroupNModes #method:getGroupNModes#

#if defined(ENABLE_OVERLOADING)
    DevicePadGetGroupNModesMethodInfo       ,
#endif
    devicePadGetGroupNModes                 ,


-- ** getNFeatures #method:getNFeatures#

#if defined(ENABLE_OVERLOADING)
    DevicePadGetNFeaturesMethodInfo         ,
#endif
    devicePadGetNFeatures                   ,


-- ** getNGroups #method:getNGroups#

#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.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.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 {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device

-- interface DevicePad 
-- | Memory-managed wrapper type.
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
/= :: DevicePad -> DevicePad -> Bool
$c/= :: DevicePad -> DevicePad -> Bool
== :: DevicePad -> DevicePad -> Bool
$c== :: 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

-- | Type class for types which can be safely cast to `DevicePad`, for instance with `toDevicePad`.
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]

-- | Cast to `DevicePad`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
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 (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

-- | Convert 'DevicePad' 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 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 (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 = ('[ '("capsLockState", Gdk.Device.DeviceCapsLockStatePropertyInfo), '("direction", Gdk.Device.DeviceDirectionPropertyInfo), '("display", Gdk.Device.DeviceDisplayPropertyInfo), '("hasBidiLayouts", Gdk.Device.DeviceHasBidiLayoutsPropertyInfo), '("hasCursor", Gdk.Device.DeviceHasCursorPropertyInfo), '("modifierState", Gdk.Device.DeviceModifierStatePropertyInfo), '("nAxes", Gdk.Device.DeviceNAxesPropertyInfo), '("name", Gdk.Device.DeviceNamePropertyInfo), '("numLockState", Gdk.Device.DeviceNumLockStatePropertyInfo), '("numTouches", Gdk.Device.DeviceNumTouchesPropertyInfo), '("productId", Gdk.Device.DeviceProductIdPropertyInfo), '("scrollLockState", Gdk.Device.DeviceScrollLockStatePropertyInfo), '("seat", Gdk.Device.DeviceSeatPropertyInfo), '("source", Gdk.Device.DeviceSourcePropertyInfo), '("tool", Gdk.Device.DeviceToolPropertyInfo), '("vendorId", Gdk.Device.DeviceVendorIdPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDevicePadMethod (t :: Symbol) (o :: *) :: * 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 "hasBidiLayouts" o = Gdk.Device.DeviceHasBidiLayoutsMethodInfo
    ResolveDevicePadMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    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 "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDevicePadMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDevicePadMethod "getCapsLockState" o = Gdk.Device.DeviceGetCapsLockStateMethodInfo
    ResolveDevicePadMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDevicePadMethod "getDeviceTool" o = Gdk.Device.DeviceGetDeviceToolMethodInfo
    ResolveDevicePadMethod "getDirection" o = Gdk.Device.DeviceGetDirectionMethodInfo
    ResolveDevicePadMethod "getDisplay" o = Gdk.Device.DeviceGetDisplayMethodInfo
    ResolveDevicePadMethod "getFeatureGroup" o = DevicePadGetFeatureGroupMethodInfo
    ResolveDevicePadMethod "getGroupNModes" o = DevicePadGetGroupNModesMethodInfo
    ResolveDevicePadMethod "getHasCursor" o = Gdk.Device.DeviceGetHasCursorMethodInfo
    ResolveDevicePadMethod "getModifierState" o = Gdk.Device.DeviceGetModifierStateMethodInfo
    ResolveDevicePadMethod "getNFeatures" o = DevicePadGetNFeaturesMethodInfo
    ResolveDevicePadMethod "getNGroups" o = DevicePadGetNGroupsMethodInfo
    ResolveDevicePadMethod "getName" o = Gdk.Device.DeviceGetNameMethodInfo
    ResolveDevicePadMethod "getNumLockState" o = Gdk.Device.DeviceGetNumLockStateMethodInfo
    ResolveDevicePadMethod "getNumTouches" o = Gdk.Device.DeviceGetNumTouchesMethodInfo
    ResolveDevicePadMethod "getProductId" o = Gdk.Device.DeviceGetProductIdMethodInfo
    ResolveDevicePadMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDevicePadMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDevicePadMethod "getScrollLockState" o = Gdk.Device.DeviceGetScrollLockStateMethodInfo
    ResolveDevicePadMethod "getSeat" o = Gdk.Device.DeviceGetSeatMethodInfo
    ResolveDevicePadMethod "getSource" o = Gdk.Device.DeviceGetSourceMethodInfo
    ResolveDevicePadMethod "getSurfaceAtPosition" o = Gdk.Device.DeviceGetSurfaceAtPositionMethodInfo
    ResolveDevicePadMethod "getVendorId" o = Gdk.Device.DeviceGetVendorIdMethodInfo
    ResolveDevicePadMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDevicePadMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    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

-- method DevicePad::get_feature_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pad"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DevicePad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevicePad" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "feature"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DevicePadFeature" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the feature type to get the group from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "feature_idx"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the index of the feature to get the group from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_pad_get_feature_group" gdk_device_pad_get_feature_group :: 
    Ptr DevicePad ->                        -- pad : TInterface (Name {namespace = "Gdk", name = "DevicePad"})
    CUInt ->                                -- feature : TInterface (Name {namespace = "Gdk", name = "DevicePadFeature"})
    Int32 ->                                -- feature_idx : TBasicType TInt
    IO Int32

-- | Returns the group the given /@feature@/ and /@idx@/ belong to,
-- or -1 if feature\/index do not exist in /@pad@/.
devicePadGetFeatureGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevicePad a) =>
    a
    -- ^ /@pad@/: a t'GI.Gdk.Interfaces.DevicePad.DevicePad'
    -> Gdk.Enums.DevicePadFeature
    -- ^ /@feature@/: the feature type to get the group from
    -> Int32
    -- ^ /@featureIdx@/: the index of the feature to get the group from
    -> m Int32
    -- ^ __Returns:__ The group number of the queried pad feature.
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 (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 (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 = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Interfaces.DevicePad.devicePadGetFeatureGroup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Interfaces-DevicePad.html#v:devicePadGetFeatureGroup"
        }


#endif

-- method DevicePad::get_group_n_modes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pad"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DevicePad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevicePad" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_idx"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "group to get the number of available modes from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_pad_get_group_n_modes" gdk_device_pad_get_group_n_modes :: 
    Ptr DevicePad ->                        -- pad : TInterface (Name {namespace = "Gdk", name = "DevicePad"})
    Int32 ->                                -- group_idx : TBasicType TInt
    IO Int32

-- | Returns the number of modes that /@group@/ may have.
devicePadGetGroupNModes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevicePad a) =>
    a
    -- ^ /@pad@/: a t'GI.Gdk.Interfaces.DevicePad.DevicePad'
    -> Int32
    -- ^ /@groupIdx@/: group to get the number of available modes from
    -> m Int32
    -- ^ __Returns:__ The number of modes available in /@group@/.
devicePadGetGroupNModes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevicePad a) =>
a -> Int32 -> m Int32
devicePadGetGroupNModes a
pad Int32
groupIdx = IO Int32 -> m Int32
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 (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 = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Interfaces.DevicePad.devicePadGetGroupNModes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Interfaces-DevicePad.html#v:devicePadGetGroupNModes"
        }


#endif

-- method DevicePad::get_n_features
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pad"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DevicePad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevicePad" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "feature"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DevicePadFeature" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pad feature" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_pad_get_n_features" gdk_device_pad_get_n_features :: 
    Ptr DevicePad ->                        -- pad : TInterface (Name {namespace = "Gdk", name = "DevicePad"})
    CUInt ->                                -- feature : TInterface (Name {namespace = "Gdk", name = "DevicePadFeature"})
    IO Int32

-- | Returns the number of features a tablet pad has.
devicePadGetNFeatures ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevicePad a) =>
    a
    -- ^ /@pad@/: a t'GI.Gdk.Interfaces.DevicePad.DevicePad'
    -> Gdk.Enums.DevicePadFeature
    -- ^ /@feature@/: a pad feature
    -> m Int32
    -- ^ __Returns:__ The amount of elements of type /@feature@/ that this pad has.
devicePadGetNFeatures :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevicePad a) =>
a -> DevicePadFeature -> m Int32
devicePadGetNFeatures a
pad DevicePadFeature
feature = IO Int32 -> m Int32
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 (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 = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Interfaces.DevicePad.devicePadGetNFeatures",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Interfaces-DevicePad.html#v:devicePadGetNFeatures"
        }


#endif

-- method DevicePad::get_n_groups
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pad"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DevicePad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevicePad" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_pad_get_n_groups" gdk_device_pad_get_n_groups :: 
    Ptr DevicePad ->                        -- pad : TInterface (Name {namespace = "Gdk", name = "DevicePad"})
    IO Int32

-- | Returns the number of groups this pad device has. Pads have
-- at least one group. A pad group is a subcollection of
-- buttons\/strip\/rings that is affected collectively by a same
-- current mode.
devicePadGetNGroups ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevicePad a) =>
    a
    -- ^ /@pad@/: a t'GI.Gdk.Interfaces.DevicePad.DevicePad'
    -> m Int32
    -- ^ __Returns:__ The number of button\/ring\/strip groups in the pad.
devicePadGetNGroups :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevicePad a) =>
a -> m Int32
devicePadGetNGroups a
pad = IO Int32 -> m Int32
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 (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 = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Interfaces.DevicePad.devicePadGetNGroups",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/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, *)])

#endif