{-# 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                   ,


 -- * 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"), [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
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== 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)
    ResolveX11DeviceManagerXI2Method        ,
#endif



 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    X11DeviceManagerXI2DisplayPropertyInfo  ,
#endif
    constructX11DeviceManagerXI2Display     ,
    getX11DeviceManagerXI2Display           ,
#if defined(ENABLE_OVERLOADING)
    x11DeviceManagerXI2Display              ,
#endif


-- ** 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.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 qualified GI.Gdk.Objects.Display as Gdk.Display

-- | Memory-managed wrapper type.
newtype X11DeviceManagerXI2 = X11DeviceManagerXI2 (SP.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)

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

foreign import ccall "gdk_x11_device_manager_xi2_get_type"
    c_gdk_x11_device_manager_xi2_get_type :: IO B.Types.GType

instance B.Types.TypedObject X11DeviceManagerXI2 where
    glibType :: IO GType
glibType = IO GType
c_gdk_x11_device_manager_xi2_get_type

instance B.Types.GObject X11DeviceManagerXI2

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

instance O.HasParentTypes X11DeviceManagerXI2
type instance O.ParentTypes X11DeviceManagerXI2 = '[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 :: (MIO.MonadIO m, IsX11DeviceManagerXI2 o) => o -> m X11DeviceManagerXI2
toX11DeviceManagerXI2 :: forall (m :: * -> *) o.
(MonadIO m, IsX11DeviceManagerXI2 o) =>
o -> m X11DeviceManagerXI2
toX11DeviceManagerXI2 = IO X11DeviceManagerXI2 -> m X11DeviceManagerXI2
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr X11DeviceManagerXI2 -> X11DeviceManagerXI2
X11DeviceManagerXI2

-- | Convert 'X11DeviceManagerXI2' 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 X11DeviceManagerXI2) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_x11_device_manager_xi2_get_type
    gvalueSet_ :: Ptr GValue -> Maybe X11DeviceManagerXI2 -> IO ()
gvalueSet_ Ptr GValue
gv Maybe X11DeviceManagerXI2
P.Nothing = Ptr GValue -> Ptr X11DeviceManagerXI2 -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr X11DeviceManagerXI2
forall a. Ptr a
FP.nullPtr :: FP.Ptr X11DeviceManagerXI2)
    gvalueSet_ Ptr GValue
gv (P.Just X11DeviceManagerXI2
obj) = X11DeviceManagerXI2 -> (Ptr X11DeviceManagerXI2 -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr X11DeviceManagerXI2
obj (Ptr GValue -> Ptr X11DeviceManagerXI2 -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe X11DeviceManagerXI2)
gvalueGet_ Ptr GValue
gv = do
        Ptr X11DeviceManagerXI2
ptr <- Ptr GValue -> IO (Ptr X11DeviceManagerXI2)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr X11DeviceManagerXI2)
        if Ptr X11DeviceManagerXI2
ptr Ptr X11DeviceManagerXI2 -> Ptr X11DeviceManagerXI2 -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr X11DeviceManagerXI2
forall a. Ptr a
FP.nullPtr
        then X11DeviceManagerXI2 -> Maybe X11DeviceManagerXI2
forall a. a -> Maybe a
P.Just (X11DeviceManagerXI2 -> Maybe X11DeviceManagerXI2)
-> IO X11DeviceManagerXI2 -> IO (Maybe X11DeviceManagerXI2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe X11DeviceManagerXI2 -> IO (Maybe X11DeviceManagerXI2)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe X11DeviceManagerXI2
forall a. Maybe a
P.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 "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 "getData" o = GObject.Object.ObjectGetDataMethodInfo
    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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveX11DeviceManagerXI2Method t X11DeviceManagerXI2, O.OverloadedMethod info X11DeviceManagerXI2 p, R.HasField t X11DeviceManagerXI2 p) => R.HasField t X11DeviceManagerXI2 p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveX11DeviceManagerXI2Method t X11DeviceManagerXI2, O.OverloadedMethodInfo info X11DeviceManagerXI2) => OL.IsLabel t (O.MethodProxy info X11DeviceManagerXI2) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

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

-- | Get the value of the “@display@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' x11DeviceManagerXI2 #display
-- @
getX11DeviceManagerXI2Display :: (MonadIO m, IsX11DeviceManagerXI2 o) => o -> m (Maybe Gdk.Display.Display)
getX11DeviceManagerXI2Display :: forall (m :: * -> *) o.
(MonadIO m, IsX11DeviceManagerXI2 o) =>
o -> m (Maybe Display)
getX11DeviceManagerXI2Display o
obj = IO (Maybe Display) -> m (Maybe Display)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Display -> Display) -> IO (Maybe Display)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"display" ManagedPtr Display -> Display
Gdk.Display.Display

-- | Construct a `GValueConstruct` with valid value for the “@display@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructX11DeviceManagerXI2Display :: (IsX11DeviceManagerXI2 o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructX11DeviceManagerXI2Display :: forall o (m :: * -> *) a.
(IsX11DeviceManagerXI2 o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructX11DeviceManagerXI2Display a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"display" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data X11DeviceManagerXI2DisplayPropertyInfo
instance AttrInfo X11DeviceManagerXI2DisplayPropertyInfo where
    type AttrAllowedOps X11DeviceManagerXI2DisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint X11DeviceManagerXI2DisplayPropertyInfo = IsX11DeviceManagerXI2
    type AttrSetTypeConstraint X11DeviceManagerXI2DisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint X11DeviceManagerXI2DisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType X11DeviceManagerXI2DisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType X11DeviceManagerXI2DisplayPropertyInfo = (Maybe Gdk.Display.Display)
    type AttrLabel X11DeviceManagerXI2DisplayPropertyInfo = "display"
    type AttrOrigin X11DeviceManagerXI2DisplayPropertyInfo = X11DeviceManagerXI2
    attrGet = getX11DeviceManagerXI2Display
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructX11DeviceManagerXI2Display
    attrClear = undefined
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsX11DeviceManagerXI2 o) =>
o -> m Int32
getX11DeviceManagerXI2Major o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructX11DeviceManagerXI2Major :: forall o (m :: * -> *).
(IsX11DeviceManagerXI2 o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructX11DeviceManagerXI2Major Int32
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"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 :: forall (m :: * -> *) o.
(MonadIO m, IsX11DeviceManagerXI2 o) =>
o -> m Int32
getX11DeviceManagerXI2Minor o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructX11DeviceManagerXI2Minor :: forall o (m :: * -> *).
(IsX11DeviceManagerXI2 o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructX11DeviceManagerXI2Minor Int32
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"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 :: forall (m :: * -> *) o.
(MonadIO m, IsX11DeviceManagerXI2 o) =>
o -> m Int32
getX11DeviceManagerXI2Opcode o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructX11DeviceManagerXI2Opcode :: forall o (m :: * -> *).
(IsX11DeviceManagerXI2 o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructX11DeviceManagerXI2Opcode Int32
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"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", X11DeviceManagerXI2DisplayPropertyInfo), '("major", X11DeviceManagerXI2MajorPropertyInfo), '("minor", X11DeviceManagerXI2MinorPropertyInfo), '("opcode", X11DeviceManagerXI2OpcodePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
x11DeviceManagerXI2Display :: AttrLabelProxy "display"
x11DeviceManagerXI2Display = AttrLabelProxy

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 = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif