{-# 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.GdkX11.Objects.X11DeviceManagerXI2
    ( 

-- * Exported types
    X11DeviceManagerXI2(..)                 ,
    IsX11DeviceManagerXI2                   ,
    toX11DeviceManagerXI2                   ,
    noX11DeviceManagerXI2                   ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveX11DeviceManagerXI2Method        ,
#endif




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

#if defined(ENABLE_OVERLOADING)
    X11DeviceManagerXI2MajorPropertyInfo    ,
#endif
    constructX11DeviceManagerXI2Major       ,
    getX11DeviceManagerXI2Major             ,
#if defined(ENABLE_OVERLOADING)
    x11DeviceManagerXI2Major                ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    X11DeviceManagerXI2MinorPropertyInfo    ,
#endif
    constructX11DeviceManagerXI2Minor       ,
    getX11DeviceManagerXI2Minor             ,
#if defined(ENABLE_OVERLOADING)
    x11DeviceManagerXI2Minor                ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    X11DeviceManagerXI2OpcodePropertyInfo   ,
#endif
    constructX11DeviceManagerXI2Opcode      ,
    getX11DeviceManagerXI2Opcode            ,
#if defined(ENABLE_OVERLOADING)
    x11DeviceManagerXI2Opcode               ,
#endif




    ) 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.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 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 qualified GI.Gdk.Objects.DeviceManager as Gdk.DeviceManager
import {-# SOURCE #-} qualified GI.GdkX11.Objects.X11DeviceManagerCore as GdkX11.X11DeviceManagerCore

-- | Memory-managed wrapper type.
newtype X11DeviceManagerXI2 = X11DeviceManagerXI2 (ManagedPtr X11DeviceManagerXI2)
    deriving (X11DeviceManagerXI2 -> X11DeviceManagerXI2 -> Bool
(X11DeviceManagerXI2 -> X11DeviceManagerXI2 -> Bool)
-> (X11DeviceManagerXI2 -> X11DeviceManagerXI2 -> Bool)
-> Eq X11DeviceManagerXI2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: X11DeviceManagerXI2 -> X11DeviceManagerXI2 -> Bool
$c/= :: X11DeviceManagerXI2 -> X11DeviceManagerXI2 -> Bool
== :: X11DeviceManagerXI2 -> X11DeviceManagerXI2 -> Bool
$c== :: X11DeviceManagerXI2 -> X11DeviceManagerXI2 -> Bool
Eq)
foreign import ccall "gdk_x11_device_manager_xi2_get_type"
    c_gdk_x11_device_manager_xi2_get_type :: IO GType

instance GObject X11DeviceManagerXI2 where
    gobjectType :: IO GType
gobjectType = IO GType
c_gdk_x11_device_manager_xi2_get_type
    

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

-- | Type class for types which can be safely cast to `X11DeviceManagerXI2`, for instance with `toX11DeviceManagerXI2`.
class (GObject o, O.IsDescendantOf X11DeviceManagerXI2 o) => IsX11DeviceManagerXI2 o
instance (GObject o, O.IsDescendantOf X11DeviceManagerXI2 o) => IsX11DeviceManagerXI2 o

instance O.HasParentTypes X11DeviceManagerXI2
type instance O.ParentTypes X11DeviceManagerXI2 = '[GdkX11.X11DeviceManagerCore.X11DeviceManagerCore, Gdk.DeviceManager.DeviceManager, GObject.Object.Object]

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

-- | A convenience alias for `Nothing` :: `Maybe` `X11DeviceManagerXI2`.
noX11DeviceManagerXI2 :: Maybe X11DeviceManagerXI2
noX11DeviceManagerXI2 :: Maybe X11DeviceManagerXI2
noX11DeviceManagerXI2 = Maybe X11DeviceManagerXI2
forall a. Maybe a
Nothing

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

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

#endif

-- VVV Prop "major"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@major@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' x11DeviceManagerXI2 #major
-- @
getX11DeviceManagerXI2Major :: (MonadIO m, IsX11DeviceManagerXI2 o) => o -> m Int32
getX11DeviceManagerXI2Major :: o -> m Int32
getX11DeviceManagerXI2Major obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "major"

-- | Construct a `GValueConstruct` with valid value for the “@major@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructX11DeviceManagerXI2Major :: (IsX11DeviceManagerXI2 o) => Int32 -> IO (GValueConstruct o)
constructX11DeviceManagerXI2Major :: Int32 -> IO (GValueConstruct o)
constructX11DeviceManagerXI2Major val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "major" Int32
val

#if defined(ENABLE_OVERLOADING)
data X11DeviceManagerXI2MajorPropertyInfo
instance AttrInfo X11DeviceManagerXI2MajorPropertyInfo where
    type AttrAllowedOps X11DeviceManagerXI2MajorPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint X11DeviceManagerXI2MajorPropertyInfo = IsX11DeviceManagerXI2
    type AttrSetTypeConstraint X11DeviceManagerXI2MajorPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint X11DeviceManagerXI2MajorPropertyInfo = (~) Int32
    type AttrTransferType X11DeviceManagerXI2MajorPropertyInfo = Int32
    type AttrGetType X11DeviceManagerXI2MajorPropertyInfo = Int32
    type AttrLabel X11DeviceManagerXI2MajorPropertyInfo = "major"
    type AttrOrigin X11DeviceManagerXI2MajorPropertyInfo = X11DeviceManagerXI2
    attrGet = getX11DeviceManagerXI2Major
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructX11DeviceManagerXI2Major
    attrClear = undefined
#endif

-- VVV Prop "minor"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@minor@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' x11DeviceManagerXI2 #minor
-- @
getX11DeviceManagerXI2Minor :: (MonadIO m, IsX11DeviceManagerXI2 o) => o -> m Int32
getX11DeviceManagerXI2Minor :: o -> m Int32
getX11DeviceManagerXI2Minor obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "minor"

-- | Construct a `GValueConstruct` with valid value for the “@minor@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructX11DeviceManagerXI2Minor :: (IsX11DeviceManagerXI2 o) => Int32 -> IO (GValueConstruct o)
constructX11DeviceManagerXI2Minor :: Int32 -> IO (GValueConstruct o)
constructX11DeviceManagerXI2Minor val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "minor" Int32
val

#if defined(ENABLE_OVERLOADING)
data X11DeviceManagerXI2MinorPropertyInfo
instance AttrInfo X11DeviceManagerXI2MinorPropertyInfo where
    type AttrAllowedOps X11DeviceManagerXI2MinorPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint X11DeviceManagerXI2MinorPropertyInfo = IsX11DeviceManagerXI2
    type AttrSetTypeConstraint X11DeviceManagerXI2MinorPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint X11DeviceManagerXI2MinorPropertyInfo = (~) Int32
    type AttrTransferType X11DeviceManagerXI2MinorPropertyInfo = Int32
    type AttrGetType X11DeviceManagerXI2MinorPropertyInfo = Int32
    type AttrLabel X11DeviceManagerXI2MinorPropertyInfo = "minor"
    type AttrOrigin X11DeviceManagerXI2MinorPropertyInfo = X11DeviceManagerXI2
    attrGet = getX11DeviceManagerXI2Minor
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructX11DeviceManagerXI2Minor
    attrClear = undefined
#endif

-- VVV Prop "opcode"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@opcode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' x11DeviceManagerXI2 #opcode
-- @
getX11DeviceManagerXI2Opcode :: (MonadIO m, IsX11DeviceManagerXI2 o) => o -> m Int32
getX11DeviceManagerXI2Opcode :: o -> m Int32
getX11DeviceManagerXI2Opcode obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "opcode"

-- | Construct a `GValueConstruct` with valid value for the “@opcode@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructX11DeviceManagerXI2Opcode :: (IsX11DeviceManagerXI2 o) => Int32 -> IO (GValueConstruct o)
constructX11DeviceManagerXI2Opcode :: Int32 -> IO (GValueConstruct o)
constructX11DeviceManagerXI2Opcode val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "opcode" Int32
val

#if defined(ENABLE_OVERLOADING)
data X11DeviceManagerXI2OpcodePropertyInfo
instance AttrInfo X11DeviceManagerXI2OpcodePropertyInfo where
    type AttrAllowedOps X11DeviceManagerXI2OpcodePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint X11DeviceManagerXI2OpcodePropertyInfo = IsX11DeviceManagerXI2
    type AttrSetTypeConstraint X11DeviceManagerXI2OpcodePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint X11DeviceManagerXI2OpcodePropertyInfo = (~) Int32
    type AttrTransferType X11DeviceManagerXI2OpcodePropertyInfo = Int32
    type AttrGetType X11DeviceManagerXI2OpcodePropertyInfo = Int32
    type AttrLabel X11DeviceManagerXI2OpcodePropertyInfo = "opcode"
    type AttrOrigin X11DeviceManagerXI2OpcodePropertyInfo = X11DeviceManagerXI2
    attrGet = getX11DeviceManagerXI2Opcode
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructX11DeviceManagerXI2Opcode
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList X11DeviceManagerXI2
type instance O.AttributeList X11DeviceManagerXI2 = X11DeviceManagerXI2AttributeList
type X11DeviceManagerXI2AttributeList = ('[ '("display", Gdk.DeviceManager.DeviceManagerDisplayPropertyInfo), '("major", X11DeviceManagerXI2MajorPropertyInfo), '("minor", X11DeviceManagerXI2MinorPropertyInfo), '("opcode", X11DeviceManagerXI2OpcodePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
x11DeviceManagerXI2Major :: AttrLabelProxy "major"
x11DeviceManagerXI2Major = AttrLabelProxy

x11DeviceManagerXI2Minor :: AttrLabelProxy "minor"
x11DeviceManagerXI2Minor = AttrLabelProxy

x11DeviceManagerXI2Opcode :: AttrLabelProxy "opcode"
x11DeviceManagerXI2Opcode = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList X11DeviceManagerXI2 = X11DeviceManagerXI2SignalList
type X11DeviceManagerXI2SignalList = ('[ '("deviceAdded", Gdk.DeviceManager.DeviceManagerDeviceAddedSignalInfo), '("deviceChanged", Gdk.DeviceManager.DeviceManagerDeviceChangedSignalInfo), '("deviceRemoved", Gdk.DeviceManager.DeviceManagerDeviceRemovedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif