{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Gdk.Objects.DeviceTool
    ( 

-- * Exported types
    DeviceTool(..)                          ,
    IsDeviceTool                            ,
    toDeviceTool                            ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDeviceToolMethod                 ,
#endif


-- ** getHardwareId #method:getHardwareId#

#if defined(ENABLE_OVERLOADING)
    DeviceToolGetHardwareIdMethodInfo       ,
#endif
    deviceToolGetHardwareId                 ,


-- ** getSerial #method:getSerial#

#if defined(ENABLE_OVERLOADING)
    DeviceToolGetSerialMethodInfo           ,
#endif
    deviceToolGetSerial                     ,


-- ** getToolType #method:getToolType#

#if defined(ENABLE_OVERLOADING)
    DeviceToolGetToolTypeMethodInfo         ,
#endif
    deviceToolGetToolType                   ,




 -- * Properties
-- ** axes #attr:axes#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DeviceToolAxesPropertyInfo              ,
#endif
    constructDeviceToolAxes                 ,
#if defined(ENABLE_OVERLOADING)
    deviceToolAxes                          ,
#endif
    getDeviceToolAxes                       ,


-- ** hardwareId #attr:hardwareId#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DeviceToolHardwareIdPropertyInfo        ,
#endif
    constructDeviceToolHardwareId           ,
#if defined(ENABLE_OVERLOADING)
    deviceToolHardwareId                    ,
#endif
    getDeviceToolHardwareId                 ,


-- ** serial #attr:serial#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DeviceToolSerialPropertyInfo            ,
#endif
    constructDeviceToolSerial               ,
#if defined(ENABLE_OVERLOADING)
    deviceToolSerial                        ,
#endif
    getDeviceToolSerial                     ,


-- ** toolType #attr:toolType#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DeviceToolToolTypePropertyInfo          ,
#endif
    constructDeviceToolToolType             ,
#if defined(ENABLE_OVERLOADING)
    deviceToolToolType                      ,
#endif
    getDeviceToolToolType                   ,




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

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

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

foreign import ccall "gdk_device_tool_get_type"
    c_gdk_device_tool_get_type :: IO B.Types.GType

instance B.Types.TypedObject DeviceTool where
    glibType :: IO GType
glibType = IO GType
c_gdk_device_tool_get_type

instance B.Types.GObject DeviceTool

-- | Convert 'DeviceTool' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DeviceTool where
    toGValue :: DeviceTool -> IO GValue
toGValue DeviceTool
o = do
        GType
gtype <- IO GType
c_gdk_device_tool_get_type
        DeviceTool -> (Ptr DeviceTool -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DeviceTool
o (GType
-> (GValue -> Ptr DeviceTool -> IO ())
-> Ptr DeviceTool
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DeviceTool -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DeviceTool
fromGValue GValue
gv = do
        Ptr DeviceTool
ptr <- GValue -> IO (Ptr DeviceTool)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DeviceTool)
        (ManagedPtr DeviceTool -> DeviceTool)
-> Ptr DeviceTool -> IO DeviceTool
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DeviceTool -> DeviceTool
DeviceTool Ptr DeviceTool
ptr
        
    

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

instance O.HasParentTypes DeviceTool
type instance O.ParentTypes DeviceTool = '[GObject.Object.Object]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceToolMethod (t :: Symbol) (o :: *) :: * where
    ResolveDeviceToolMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDeviceToolMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDeviceToolMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDeviceToolMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDeviceToolMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDeviceToolMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDeviceToolMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDeviceToolMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDeviceToolMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDeviceToolMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDeviceToolMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDeviceToolMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDeviceToolMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDeviceToolMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDeviceToolMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDeviceToolMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDeviceToolMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDeviceToolMethod "getHardwareId" o = DeviceToolGetHardwareIdMethodInfo
    ResolveDeviceToolMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDeviceToolMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDeviceToolMethod "getSerial" o = DeviceToolGetSerialMethodInfo
    ResolveDeviceToolMethod "getToolType" o = DeviceToolGetToolTypeMethodInfo
    ResolveDeviceToolMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDeviceToolMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDeviceToolMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDeviceToolMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDeviceToolMethod t DeviceTool, O.MethodInfo info DeviceTool p) => OL.IsLabel t (DeviceTool -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- VVV Prop "axes"
   -- Type: TInterface (Name {namespace = "Gdk", name = "AxisFlags"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@axes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' deviceTool #axes
-- @
getDeviceToolAxes :: (MonadIO m, IsDeviceTool o) => o -> m [Gdk.Flags.AxisFlags]
getDeviceToolAxes :: o -> m [AxisFlags]
getDeviceToolAxes o
obj = IO [AxisFlags] -> m [AxisFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [AxisFlags] -> m [AxisFlags])
-> IO [AxisFlags] -> m [AxisFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [AxisFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"axes"

-- | Construct a `GValueConstruct` with valid value for the “@axes@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceToolAxes :: (IsDeviceTool o, MIO.MonadIO m) => [Gdk.Flags.AxisFlags] -> m (GValueConstruct o)
constructDeviceToolAxes :: [AxisFlags] -> m (GValueConstruct o)
constructDeviceToolAxes [AxisFlags]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> [AxisFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"axes" [AxisFlags]
val

#if defined(ENABLE_OVERLOADING)
data DeviceToolAxesPropertyInfo
instance AttrInfo DeviceToolAxesPropertyInfo where
    type AttrAllowedOps DeviceToolAxesPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceToolAxesPropertyInfo = IsDeviceTool
    type AttrSetTypeConstraint DeviceToolAxesPropertyInfo = (~) [Gdk.Flags.AxisFlags]
    type AttrTransferTypeConstraint DeviceToolAxesPropertyInfo = (~) [Gdk.Flags.AxisFlags]
    type AttrTransferType DeviceToolAxesPropertyInfo = [Gdk.Flags.AxisFlags]
    type AttrGetType DeviceToolAxesPropertyInfo = [Gdk.Flags.AxisFlags]
    type AttrLabel DeviceToolAxesPropertyInfo = "axes"
    type AttrOrigin DeviceToolAxesPropertyInfo = DeviceTool
    attrGet = getDeviceToolAxes
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceToolAxes
    attrClear = undefined
#endif

-- VVV Prop "hardware-id"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@hardware-id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' deviceTool #hardwareId
-- @
getDeviceToolHardwareId :: (MonadIO m, IsDeviceTool o) => o -> m Word64
getDeviceToolHardwareId :: o -> m Word64
getDeviceToolHardwareId o
obj = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word64
forall a. GObject a => a -> String -> IO Word64
B.Properties.getObjectPropertyUInt64 o
obj String
"hardware-id"

-- | Construct a `GValueConstruct` with valid value for the “@hardware-id@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceToolHardwareId :: (IsDeviceTool o, MIO.MonadIO m) => Word64 -> m (GValueConstruct o)
constructDeviceToolHardwareId :: Word64 -> m (GValueConstruct o)
constructDeviceToolHardwareId Word64
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Word64 -> IO (GValueConstruct o)
forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 String
"hardware-id" Word64
val

#if defined(ENABLE_OVERLOADING)
data DeviceToolHardwareIdPropertyInfo
instance AttrInfo DeviceToolHardwareIdPropertyInfo where
    type AttrAllowedOps DeviceToolHardwareIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceToolHardwareIdPropertyInfo = IsDeviceTool
    type AttrSetTypeConstraint DeviceToolHardwareIdPropertyInfo = (~) Word64
    type AttrTransferTypeConstraint DeviceToolHardwareIdPropertyInfo = (~) Word64
    type AttrTransferType DeviceToolHardwareIdPropertyInfo = Word64
    type AttrGetType DeviceToolHardwareIdPropertyInfo = Word64
    type AttrLabel DeviceToolHardwareIdPropertyInfo = "hardware-id"
    type AttrOrigin DeviceToolHardwareIdPropertyInfo = DeviceTool
    attrGet = getDeviceToolHardwareId
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceToolHardwareId
    attrClear = undefined
#endif

-- VVV Prop "serial"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@serial@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' deviceTool #serial
-- @
getDeviceToolSerial :: (MonadIO m, IsDeviceTool o) => o -> m Word64
getDeviceToolSerial :: o -> m Word64
getDeviceToolSerial o
obj = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word64
forall a. GObject a => a -> String -> IO Word64
B.Properties.getObjectPropertyUInt64 o
obj String
"serial"

-- | Construct a `GValueConstruct` with valid value for the “@serial@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceToolSerial :: (IsDeviceTool o, MIO.MonadIO m) => Word64 -> m (GValueConstruct o)
constructDeviceToolSerial :: Word64 -> m (GValueConstruct o)
constructDeviceToolSerial Word64
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Word64 -> IO (GValueConstruct o)
forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 String
"serial" Word64
val

#if defined(ENABLE_OVERLOADING)
data DeviceToolSerialPropertyInfo
instance AttrInfo DeviceToolSerialPropertyInfo where
    type AttrAllowedOps DeviceToolSerialPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceToolSerialPropertyInfo = IsDeviceTool
    type AttrSetTypeConstraint DeviceToolSerialPropertyInfo = (~) Word64
    type AttrTransferTypeConstraint DeviceToolSerialPropertyInfo = (~) Word64
    type AttrTransferType DeviceToolSerialPropertyInfo = Word64
    type AttrGetType DeviceToolSerialPropertyInfo = Word64
    type AttrLabel DeviceToolSerialPropertyInfo = "serial"
    type AttrOrigin DeviceToolSerialPropertyInfo = DeviceTool
    attrGet = getDeviceToolSerial
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceToolSerial
    attrClear = undefined
#endif

-- VVV Prop "tool-type"
   -- Type: TInterface (Name {namespace = "Gdk", name = "DeviceToolType"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@tool-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' deviceTool #toolType
-- @
getDeviceToolToolType :: (MonadIO m, IsDeviceTool o) => o -> m Gdk.Enums.DeviceToolType
getDeviceToolToolType :: o -> m DeviceToolType
getDeviceToolToolType o
obj = IO DeviceToolType -> m DeviceToolType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceToolType -> m DeviceToolType)
-> IO DeviceToolType -> m DeviceToolType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO DeviceToolType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"tool-type"

-- | Construct a `GValueConstruct` with valid value for the “@tool-type@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceToolToolType :: (IsDeviceTool o, MIO.MonadIO m) => Gdk.Enums.DeviceToolType -> m (GValueConstruct o)
constructDeviceToolToolType :: DeviceToolType -> m (GValueConstruct o)
constructDeviceToolToolType DeviceToolType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> DeviceToolType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"tool-type" DeviceToolType
val

#if defined(ENABLE_OVERLOADING)
data DeviceToolToolTypePropertyInfo
instance AttrInfo DeviceToolToolTypePropertyInfo where
    type AttrAllowedOps DeviceToolToolTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceToolToolTypePropertyInfo = IsDeviceTool
    type AttrSetTypeConstraint DeviceToolToolTypePropertyInfo = (~) Gdk.Enums.DeviceToolType
    type AttrTransferTypeConstraint DeviceToolToolTypePropertyInfo = (~) Gdk.Enums.DeviceToolType
    type AttrTransferType DeviceToolToolTypePropertyInfo = Gdk.Enums.DeviceToolType
    type AttrGetType DeviceToolToolTypePropertyInfo = Gdk.Enums.DeviceToolType
    type AttrLabel DeviceToolToolTypePropertyInfo = "tool-type"
    type AttrOrigin DeviceToolToolTypePropertyInfo = DeviceTool
    attrGet = getDeviceToolToolType
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceToolToolType
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DeviceTool
type instance O.AttributeList DeviceTool = DeviceToolAttributeList
type DeviceToolAttributeList = ('[ '("axes", DeviceToolAxesPropertyInfo), '("hardwareId", DeviceToolHardwareIdPropertyInfo), '("serial", DeviceToolSerialPropertyInfo), '("toolType", DeviceToolToolTypePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
deviceToolAxes :: AttrLabelProxy "axes"
deviceToolAxes = AttrLabelProxy

deviceToolHardwareId :: AttrLabelProxy "hardwareId"
deviceToolHardwareId = AttrLabelProxy

deviceToolSerial :: AttrLabelProxy "serial"
deviceToolSerial = AttrLabelProxy

deviceToolToolType :: AttrLabelProxy "toolType"
deviceToolToolType = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DeviceTool = DeviceToolSignalList
type DeviceToolSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gdk_device_tool_get_hardware_id" gdk_device_tool_get_hardware_id :: 
    Ptr DeviceTool ->                       -- tool : TInterface (Name {namespace = "Gdk", name = "DeviceTool"})
    IO Word64

-- | Gets the hardware ID of this tool, or 0 if it\'s not known. When
-- non-zero, the identificator is unique for the given tool model,
-- meaning that two identical tools will share the same /@hardwareId@/,
-- but will have different serial numbers (see 'GI.Gdk.Objects.DeviceTool.deviceToolGetSerial').
-- 
-- This is a more concrete (and device specific) method to identify
-- a t'GI.Gdk.Objects.DeviceTool.DeviceTool' than 'GI.Gdk.Objects.DeviceTool.deviceToolGetToolType', as a tablet
-- may support multiple devices with the same t'GI.Gdk.Enums.DeviceToolType',
-- but having different hardware identificators.
-- 
-- /Since: 3.22/
deviceToolGetHardwareId ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceTool a) =>
    a
    -- ^ /@tool@/: a t'GI.Gdk.Objects.DeviceTool.DeviceTool'
    -> m Word64
    -- ^ __Returns:__ The hardware identificator of this tool.
deviceToolGetHardwareId :: a -> m Word64
deviceToolGetHardwareId a
tool = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceTool
tool' <- a -> IO (Ptr DeviceTool)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tool
    Word64
result <- Ptr DeviceTool -> IO Word64
gdk_device_tool_get_hardware_id Ptr DeviceTool
tool'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
tool
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data DeviceToolGetHardwareIdMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsDeviceTool a) => O.MethodInfo DeviceToolGetHardwareIdMethodInfo a signature where
    overloadedMethod = deviceToolGetHardwareId

#endif

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

foreign import ccall "gdk_device_tool_get_serial" gdk_device_tool_get_serial :: 
    Ptr DeviceTool ->                       -- tool : TInterface (Name {namespace = "Gdk", name = "DeviceTool"})
    IO Word64

-- | Gets the serial of this tool, this value can be used to identify a
-- physical tool (eg. a tablet pen) across program executions.
-- 
-- /Since: 3.22/
deviceToolGetSerial ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceTool a) =>
    a
    -- ^ /@tool@/: a t'GI.Gdk.Objects.DeviceTool.DeviceTool'
    -> m Word64
    -- ^ __Returns:__ The serial ID for this tool
deviceToolGetSerial :: a -> m Word64
deviceToolGetSerial a
tool = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceTool
tool' <- a -> IO (Ptr DeviceTool)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tool
    Word64
result <- Ptr DeviceTool -> IO Word64
gdk_device_tool_get_serial Ptr DeviceTool
tool'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
tool
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data DeviceToolGetSerialMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsDeviceTool a) => O.MethodInfo DeviceToolGetSerialMethodInfo a signature where
    overloadedMethod = deviceToolGetSerial

#endif

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

foreign import ccall "gdk_device_tool_get_tool_type" gdk_device_tool_get_tool_type :: 
    Ptr DeviceTool ->                       -- tool : TInterface (Name {namespace = "Gdk", name = "DeviceTool"})
    IO CUInt

-- | Gets the t'GI.Gdk.Enums.DeviceToolType' of the tool.
-- 
-- /Since: 3.22/
deviceToolGetToolType ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceTool a) =>
    a
    -- ^ /@tool@/: a t'GI.Gdk.Objects.DeviceTool.DeviceTool'
    -> m Gdk.Enums.DeviceToolType
    -- ^ __Returns:__ The physical type for this tool. This can be used to figure out what
    -- sort of pen is being used, such as an airbrush or a pencil.
deviceToolGetToolType :: a -> m DeviceToolType
deviceToolGetToolType a
tool = IO DeviceToolType -> m DeviceToolType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceToolType -> m DeviceToolType)
-> IO DeviceToolType -> m DeviceToolType
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceTool
tool' <- a -> IO (Ptr DeviceTool)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
tool
    CUInt
result <- Ptr DeviceTool -> IO CUInt
gdk_device_tool_get_tool_type Ptr DeviceTool
tool'
    let result' :: DeviceToolType
result' = (Int -> DeviceToolType
forall a. Enum a => Int -> a
toEnum (Int -> DeviceToolType)
-> (CUInt -> Int) -> CUInt -> DeviceToolType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
tool
    DeviceToolType -> IO DeviceToolType
forall (m :: * -> *) a. Monad m => a -> m a
return DeviceToolType
result'

#if defined(ENABLE_OVERLOADING)
data DeviceToolGetToolTypeMethodInfo
instance (signature ~ (m Gdk.Enums.DeviceToolType), MonadIO m, IsDeviceTool a) => O.MethodInfo DeviceToolGetToolTypeMethodInfo a signature where
    overloadedMethod = deviceToolGetToolType

#endif