{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.DeviceTool
(
DeviceTool(..) ,
IsDeviceTool ,
toDeviceTool ,
#if defined(ENABLE_OVERLOADING)
ResolveDeviceToolMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceToolGetHardwareIdMethodInfo ,
#endif
deviceToolGetHardwareId ,
#if defined(ENABLE_OVERLOADING)
DeviceToolGetSerialMethodInfo ,
#endif
deviceToolGetSerial ,
#if defined(ENABLE_OVERLOADING)
DeviceToolGetToolTypeMethodInfo ,
#endif
deviceToolGetToolType ,
#if defined(ENABLE_OVERLOADING)
DeviceToolAxesPropertyInfo ,
#endif
constructDeviceToolAxes ,
#if defined(ENABLE_OVERLOADING)
deviceToolAxes ,
#endif
getDeviceToolAxes ,
#if defined(ENABLE_OVERLOADING)
DeviceToolHardwareIdPropertyInfo ,
#endif
constructDeviceToolHardwareId ,
#if defined(ENABLE_OVERLOADING)
deviceToolHardwareId ,
#endif
getDeviceToolHardwareId ,
#if defined(ENABLE_OVERLOADING)
DeviceToolSerialPropertyInfo ,
#endif
constructDeviceToolSerial ,
#if defined(ENABLE_OVERLOADING)
deviceToolSerial ,
#endif
getDeviceToolSerial ,
#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
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
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
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]
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
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"
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
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"
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
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"
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
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"
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
foreign import ccall "gdk_device_tool_get_hardware_id" gdk_device_tool_get_hardware_id ::
Ptr DeviceTool ->
IO Word64
deviceToolGetHardwareId ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceTool a) =>
a
-> m Word64
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
foreign import ccall "gdk_device_tool_get_serial" gdk_device_tool_get_serial ::
Ptr DeviceTool ->
IO Word64
deviceToolGetSerial ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceTool a) =>
a
-> m Word64
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
foreign import ccall "gdk_device_tool_get_tool_type" gdk_device_tool_get_tool_type ::
Ptr DeviceTool ->
IO CUInt
deviceToolGetToolType ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceTool a) =>
a
-> m Gdk.Enums.DeviceToolType
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