{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Clutter.Objects.DeviceManager.DeviceManager' structure contains only private data
-- 
-- /Since: 1.2/

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

module GI.Clutter.Objects.DeviceManager
    ( 

-- * Exported types
    DeviceManager(..)                       ,
    IsDeviceManager                         ,
    toDeviceManager                         ,


 -- * 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"), [listDevices]("GI.Clutter.Objects.DeviceManager#g:method:listDevices"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [peekDevices]("GI.Clutter.Objects.DeviceManager#g:method:peekDevices"), [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
-- [getCoreDevice]("GI.Clutter.Objects.DeviceManager#g:method:getCoreDevice"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDevice]("GI.Clutter.Objects.DeviceManager#g:method:getDevice"), [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)
    ResolveDeviceManagerMethod              ,
#endif

-- ** getCoreDevice #method:getCoreDevice#

#if defined(ENABLE_OVERLOADING)
    DeviceManagerGetCoreDeviceMethodInfo    ,
#endif
    deviceManagerGetCoreDevice              ,


-- ** getDefault #method:getDefault#

    deviceManagerGetDefault                 ,


-- ** getDevice #method:getDevice#

#if defined(ENABLE_OVERLOADING)
    DeviceManagerGetDeviceMethodInfo        ,
#endif
    deviceManagerGetDevice                  ,


-- ** listDevices #method:listDevices#

#if defined(ENABLE_OVERLOADING)
    DeviceManagerListDevicesMethodInfo      ,
#endif
    deviceManagerListDevices                ,


-- ** peekDevices #method:peekDevices#

#if defined(ENABLE_OVERLOADING)
    DeviceManagerPeekDevicesMethodInfo      ,
#endif
    deviceManagerPeekDevices                ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DeviceManagerBackendPropertyInfo        ,
#endif
    constructDeviceManagerBackend           ,
#if defined(ENABLE_OVERLOADING)
    deviceManagerBackend                    ,
#endif
    getDeviceManagerBackend                 ,




 -- * Signals


-- ** deviceAdded #signal:deviceAdded#

    DeviceManagerDeviceAddedCallback        ,
#if defined(ENABLE_OVERLOADING)
    DeviceManagerDeviceAddedSignalInfo      ,
#endif
    afterDeviceManagerDeviceAdded           ,
    onDeviceManagerDeviceAdded              ,


-- ** deviceRemoved #signal:deviceRemoved#

    DeviceManagerDeviceRemovedCallback      ,
#if defined(ENABLE_OVERLOADING)
    DeviceManagerDeviceRemovedSignalInfo    ,
#endif
    afterDeviceManagerDeviceRemoved         ,
    onDeviceManagerDeviceRemoved            ,




    ) 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.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.RectangleInt as Cairo.RectangleInt
import qualified GI.Clutter.Callbacks as Clutter.Callbacks
import {-# SOURCE #-} qualified GI.Clutter.Enums as Clutter.Enums
import {-# SOURCE #-} qualified GI.Clutter.Flags as Clutter.Flags
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Animatable as Clutter.Animatable
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Container as Clutter.Container
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Content as Clutter.Content
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Scriptable as Clutter.Scriptable
import {-# SOURCE #-} qualified GI.Clutter.Objects.Action as Clutter.Action
import {-# SOURCE #-} qualified GI.Clutter.Objects.Actor as Clutter.Actor
import {-# SOURCE #-} qualified GI.Clutter.Objects.ActorMeta as Clutter.ActorMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Alpha as Clutter.Alpha
import {-# SOURCE #-} qualified GI.Clutter.Objects.Animation as Clutter.Animation
import {-# SOURCE #-} qualified GI.Clutter.Objects.Animator as Clutter.Animator
import {-# SOURCE #-} qualified GI.Clutter.Objects.Backend as Clutter.Backend
import {-# SOURCE #-} qualified GI.Clutter.Objects.ChildMeta as Clutter.ChildMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Constraint as Clutter.Constraint
import {-# SOURCE #-} qualified GI.Clutter.Objects.Effect as Clutter.Effect
import {-# SOURCE #-} qualified GI.Clutter.Objects.Group as Clutter.Group
import {-# SOURCE #-} qualified GI.Clutter.Objects.InputDevice as Clutter.InputDevice
import {-# SOURCE #-} qualified GI.Clutter.Objects.Interval as Clutter.Interval
import {-# SOURCE #-} qualified GI.Clutter.Objects.LayoutManager as Clutter.LayoutManager
import {-# SOURCE #-} qualified GI.Clutter.Objects.LayoutMeta as Clutter.LayoutMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Script as Clutter.Script
import {-# SOURCE #-} qualified GI.Clutter.Objects.Shader as Clutter.Shader
import {-# SOURCE #-} qualified GI.Clutter.Objects.Stage as Clutter.Stage
import {-# SOURCE #-} qualified GI.Clutter.Objects.State as Clutter.State
import {-# SOURCE #-} qualified GI.Clutter.Objects.Timeline as Clutter.Timeline
import {-# SOURCE #-} qualified GI.Clutter.Objects.Transition as Clutter.Transition
import {-# SOURCE #-} qualified GI.Clutter.Structs.ActorBox as Clutter.ActorBox
import {-# SOURCE #-} qualified GI.Clutter.Structs.AnimatorKey as Clutter.AnimatorKey
import {-# SOURCE #-} qualified GI.Clutter.Structs.ButtonEvent as Clutter.ButtonEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Color as Clutter.Color
import {-# SOURCE #-} qualified GI.Clutter.Structs.CrossingEvent as Clutter.CrossingEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.EventSequence as Clutter.EventSequence
import {-# SOURCE #-} qualified GI.Clutter.Structs.Fog as Clutter.Fog
import {-# SOURCE #-} qualified GI.Clutter.Structs.Geometry as Clutter.Geometry
import {-# SOURCE #-} qualified GI.Clutter.Structs.KeyEvent as Clutter.KeyEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Margin as Clutter.Margin
import {-# SOURCE #-} qualified GI.Clutter.Structs.Matrix as Clutter.Matrix
import {-# SOURCE #-} qualified GI.Clutter.Structs.MotionEvent as Clutter.MotionEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.PaintVolume as Clutter.PaintVolume
import {-# SOURCE #-} qualified GI.Clutter.Structs.Perspective as Clutter.Perspective
import {-# SOURCE #-} qualified GI.Clutter.Structs.Point as Clutter.Point
import {-# SOURCE #-} qualified GI.Clutter.Structs.Rect as Clutter.Rect
import {-# SOURCE #-} qualified GI.Clutter.Structs.ScrollEvent as Clutter.ScrollEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Size as Clutter.Size
import {-# SOURCE #-} qualified GI.Clutter.Structs.StateKey as Clutter.StateKey
import {-# SOURCE #-} qualified GI.Clutter.Structs.Vertex as Clutter.Vertex
import {-# SOURCE #-} qualified GI.Clutter.Unions.Event as Clutter.Event
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.ObjectClass as GObject.ObjectClass
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Json.Structs.Node as Json.Node
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.Layout as Pango.Layout

#else
import {-# SOURCE #-} qualified GI.Clutter.Enums as Clutter.Enums
import {-# SOURCE #-} qualified GI.Clutter.Objects.Backend as Clutter.Backend
import {-# SOURCE #-} qualified GI.Clutter.Objects.InputDevice as Clutter.InputDevice
import qualified GI.GObject.Objects.Object as GObject.Object

#endif

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

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

foreign import ccall "clutter_device_manager_get_type"
    c_clutter_device_manager_get_type :: IO B.Types.GType

instance B.Types.TypedObject DeviceManager where
    glibType :: IO GType
glibType = IO GType
c_clutter_device_manager_get_type

instance B.Types.GObject DeviceManager

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceManagerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDeviceManagerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDeviceManagerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDeviceManagerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDeviceManagerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDeviceManagerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDeviceManagerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDeviceManagerMethod "listDevices" o = DeviceManagerListDevicesMethodInfo
    ResolveDeviceManagerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDeviceManagerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDeviceManagerMethod "peekDevices" o = DeviceManagerPeekDevicesMethodInfo
    ResolveDeviceManagerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDeviceManagerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDeviceManagerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDeviceManagerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDeviceManagerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDeviceManagerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDeviceManagerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDeviceManagerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDeviceManagerMethod "getCoreDevice" o = DeviceManagerGetCoreDeviceMethodInfo
    ResolveDeviceManagerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDeviceManagerMethod "getDevice" o = DeviceManagerGetDeviceMethodInfo
    ResolveDeviceManagerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDeviceManagerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDeviceManagerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDeviceManagerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDeviceManagerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDeviceManagerMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDeviceManagerMethod t DeviceManager, O.OverloadedMethod info DeviceManager p) => OL.IsLabel t (DeviceManager -> 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 ~ ResolveDeviceManagerMethod t DeviceManager, O.OverloadedMethod info DeviceManager p, R.HasField t DeviceManager p) => R.HasField t DeviceManager p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- signal DeviceManager::device-added
-- | The [deviceAdded](#g:signal:deviceAdded) signal is emitted each time a device has been
-- added to the t'GI.Clutter.Objects.DeviceManager.DeviceManager'
-- 
-- /Since: 1.2/
type DeviceManagerDeviceAddedCallback =
    Clutter.InputDevice.InputDevice
    -- ^ /@device@/: the newly added t'GI.Clutter.Objects.InputDevice.InputDevice'
    -> IO ()

type C_DeviceManagerDeviceAddedCallback =
    Ptr DeviceManager ->                    -- object
    Ptr Clutter.InputDevice.InputDevice ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DeviceManagerDeviceAddedCallback`.
foreign import ccall "wrapper"
    mk_DeviceManagerDeviceAddedCallback :: C_DeviceManagerDeviceAddedCallback -> IO (FunPtr C_DeviceManagerDeviceAddedCallback)

wrap_DeviceManagerDeviceAddedCallback :: 
    GObject a => (a -> DeviceManagerDeviceAddedCallback) ->
    C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceAddedCallback :: forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceAddedCallback a -> DeviceManagerDeviceAddedCallback
gi'cb Ptr DeviceManager
gi'selfPtr Ptr InputDevice
device Ptr ()
_ = do
    InputDevice
device' <- ((ManagedPtr InputDevice -> InputDevice)
-> Ptr InputDevice -> IO InputDevice
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputDevice -> InputDevice
Clutter.InputDevice.InputDevice) Ptr InputDevice
device
    Ptr DeviceManager -> (DeviceManager -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DeviceManager
gi'selfPtr ((DeviceManager -> IO ()) -> IO ())
-> (DeviceManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DeviceManager
gi'self -> a -> DeviceManagerDeviceAddedCallback
gi'cb (DeviceManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DeviceManager
gi'self)  InputDevice
device'


-- | Connect a signal handler for the [deviceAdded](#signal:deviceAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' deviceManager #deviceAdded callback
-- @
-- 
-- 
onDeviceManagerDeviceAdded :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceAddedCallback) -> m SignalHandlerId
onDeviceManagerDeviceAdded :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
onDeviceManagerDeviceAdded a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
    let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceAddedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
    FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceAddedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
    a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-added" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [deviceAdded](#signal:deviceAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' deviceManager #deviceAdded callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDeviceManagerDeviceAdded :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceAddedCallback) -> m SignalHandlerId
afterDeviceManagerDeviceAdded :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
afterDeviceManagerDeviceAdded a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
    let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceAddedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
    FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceAddedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
    a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-added" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DeviceManagerDeviceAddedSignalInfo
instance SignalInfo DeviceManagerDeviceAddedSignalInfo where
    type HaskellCallbackType DeviceManagerDeviceAddedSignalInfo = DeviceManagerDeviceAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DeviceManagerDeviceAddedCallback cb
        cb'' <- mk_DeviceManagerDeviceAddedCallback cb'
        connectSignalFunPtr obj "device-added" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.DeviceManager::device-added"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeviceManager.html#g:signal:deviceAdded"})

#endif

-- signal DeviceManager::device-removed
-- | The [deviceRemoved](#g:signal:deviceRemoved) signal is emitted each time a device has been
-- removed from the t'GI.Clutter.Objects.DeviceManager.DeviceManager'
-- 
-- /Since: 1.2/
type DeviceManagerDeviceRemovedCallback =
    Clutter.InputDevice.InputDevice
    -- ^ /@device@/: the removed t'GI.Clutter.Objects.InputDevice.InputDevice'
    -> IO ()

type C_DeviceManagerDeviceRemovedCallback =
    Ptr DeviceManager ->                    -- object
    Ptr Clutter.InputDevice.InputDevice ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DeviceManagerDeviceRemovedCallback`.
foreign import ccall "wrapper"
    mk_DeviceManagerDeviceRemovedCallback :: C_DeviceManagerDeviceRemovedCallback -> IO (FunPtr C_DeviceManagerDeviceRemovedCallback)

wrap_DeviceManagerDeviceRemovedCallback :: 
    GObject a => (a -> DeviceManagerDeviceRemovedCallback) ->
    C_DeviceManagerDeviceRemovedCallback
wrap_DeviceManagerDeviceRemovedCallback :: forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceRemovedCallback a -> DeviceManagerDeviceAddedCallback
gi'cb Ptr DeviceManager
gi'selfPtr Ptr InputDevice
device Ptr ()
_ = do
    InputDevice
device' <- ((ManagedPtr InputDevice -> InputDevice)
-> Ptr InputDevice -> IO InputDevice
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputDevice -> InputDevice
Clutter.InputDevice.InputDevice) Ptr InputDevice
device
    Ptr DeviceManager -> (DeviceManager -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DeviceManager
gi'selfPtr ((DeviceManager -> IO ()) -> IO ())
-> (DeviceManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DeviceManager
gi'self -> a -> DeviceManagerDeviceAddedCallback
gi'cb (DeviceManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DeviceManager
gi'self)  InputDevice
device'


-- | Connect a signal handler for the [deviceRemoved](#signal:deviceRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' deviceManager #deviceRemoved callback
-- @
-- 
-- 
onDeviceManagerDeviceRemoved :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceRemovedCallback) -> m SignalHandlerId
onDeviceManagerDeviceRemoved :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
onDeviceManagerDeviceRemoved a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
    let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceRemovedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
    FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceRemovedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
    a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-removed" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [deviceRemoved](#signal:deviceRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' deviceManager #deviceRemoved callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDeviceManagerDeviceRemoved :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceRemovedCallback) -> m SignalHandlerId
afterDeviceManagerDeviceRemoved :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
afterDeviceManagerDeviceRemoved a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
    let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceRemovedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
    FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceRemovedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
    a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-removed" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DeviceManagerDeviceRemovedSignalInfo
instance SignalInfo DeviceManagerDeviceRemovedSignalInfo where
    type HaskellCallbackType DeviceManagerDeviceRemovedSignalInfo = DeviceManagerDeviceRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DeviceManagerDeviceRemovedCallback cb
        cb'' <- mk_DeviceManagerDeviceRemovedCallback cb'
        connectSignalFunPtr obj "device-removed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.DeviceManager::device-removed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeviceManager.html#g:signal:deviceRemoved"})

#endif

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

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

-- | Construct a `GValueConstruct` with valid value for the “@backend@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceManagerBackend :: (IsDeviceManager o, MIO.MonadIO m, Clutter.Backend.IsBackend a) => a -> m (GValueConstruct o)
constructDeviceManagerBackend :: forall o (m :: * -> *) a.
(IsDeviceManager o, MonadIO m, IsBackend a) =>
a -> m (GValueConstruct o)
constructDeviceManagerBackend a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"backend" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data DeviceManagerBackendPropertyInfo
instance AttrInfo DeviceManagerBackendPropertyInfo where
    type AttrAllowedOps DeviceManagerBackendPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceManagerBackendPropertyInfo = IsDeviceManager
    type AttrSetTypeConstraint DeviceManagerBackendPropertyInfo = Clutter.Backend.IsBackend
    type AttrTransferTypeConstraint DeviceManagerBackendPropertyInfo = Clutter.Backend.IsBackend
    type AttrTransferType DeviceManagerBackendPropertyInfo = Clutter.Backend.Backend
    type AttrGetType DeviceManagerBackendPropertyInfo = (Maybe Clutter.Backend.Backend)
    type AttrLabel DeviceManagerBackendPropertyInfo = "backend"
    type AttrOrigin DeviceManagerBackendPropertyInfo = DeviceManager
    attrGet = getDeviceManagerBackend
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Clutter.Backend.Backend v
    attrConstruct = constructDeviceManagerBackend
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.DeviceManager.backend"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeviceManager.html#g:attr:backend"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DeviceManager
type instance O.AttributeList DeviceManager = DeviceManagerAttributeList
type DeviceManagerAttributeList = ('[ '("backend", DeviceManagerBackendPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
deviceManagerBackend :: AttrLabelProxy "backend"
deviceManagerBackend = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DeviceManager = DeviceManagerSignalList
type DeviceManagerSignalList = ('[ '("deviceAdded", DeviceManagerDeviceAddedSignalInfo), '("deviceRemoved", DeviceManagerDeviceRemovedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method DeviceManager::get_core_device
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device_manager"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "DeviceManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterDeviceManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "device_type"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "InputDeviceType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the type of the core device"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "InputDevice" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_device_manager_get_core_device" clutter_device_manager_get_core_device :: 
    Ptr DeviceManager ->                    -- device_manager : TInterface (Name {namespace = "Clutter", name = "DeviceManager"})
    CUInt ->                                -- device_type : TInterface (Name {namespace = "Clutter", name = "InputDeviceType"})
    IO (Ptr Clutter.InputDevice.InputDevice)

-- | Retrieves the core t'GI.Clutter.Objects.InputDevice.InputDevice' of type /@deviceType@/
-- 
-- Core devices are devices created automatically by the default
-- Clutter backend
-- 
-- /Since: 1.2/
deviceManagerGetCoreDevice ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceManager a) =>
    a
    -- ^ /@deviceManager@/: a t'GI.Clutter.Objects.DeviceManager.DeviceManager'
    -> Clutter.Enums.InputDeviceType
    -- ^ /@deviceType@/: the type of the core device
    -> m Clutter.InputDevice.InputDevice
    -- ^ __Returns:__ a t'GI.Clutter.Objects.InputDevice.InputDevice' or 'P.Nothing'. The
    --   returned device is owned by the t'GI.Clutter.Objects.DeviceManager.DeviceManager' and should
    --   not be modified or freed
deviceManagerGetCoreDevice :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceManager a) =>
a -> InputDeviceType -> m InputDevice
deviceManagerGetCoreDevice a
deviceManager InputDeviceType
deviceType = IO InputDevice -> m InputDevice
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputDevice -> m InputDevice)
-> IO InputDevice -> m InputDevice
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceManager
deviceManager' <- a -> IO (Ptr DeviceManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
deviceManager
    let deviceType' :: CUInt
deviceType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (InputDeviceType -> Int) -> InputDeviceType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputDeviceType -> Int
forall a. Enum a => a -> Int
fromEnum) InputDeviceType
deviceType
    Ptr InputDevice
result <- Ptr DeviceManager -> CUInt -> IO (Ptr InputDevice)
clutter_device_manager_get_core_device Ptr DeviceManager
deviceManager' CUInt
deviceType'
    Text -> Ptr InputDevice -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceManagerGetCoreDevice" Ptr InputDevice
result
    InputDevice
result' <- ((ManagedPtr InputDevice -> InputDevice)
-> Ptr InputDevice -> IO InputDevice
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputDevice -> InputDevice
Clutter.InputDevice.InputDevice) Ptr InputDevice
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
deviceManager
    InputDevice -> IO InputDevice
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return InputDevice
result'

#if defined(ENABLE_OVERLOADING)
data DeviceManagerGetCoreDeviceMethodInfo
instance (signature ~ (Clutter.Enums.InputDeviceType -> m Clutter.InputDevice.InputDevice), MonadIO m, IsDeviceManager a) => O.OverloadedMethod DeviceManagerGetCoreDeviceMethodInfo a signature where
    overloadedMethod = deviceManagerGetCoreDevice

instance O.OverloadedMethodInfo DeviceManagerGetCoreDeviceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.DeviceManager.deviceManagerGetCoreDevice",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeviceManager.html#v:deviceManagerGetCoreDevice"
        })


#endif

-- method DeviceManager::get_device
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device_manager"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "DeviceManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterDeviceManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "device_id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the integer id of a device"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "InputDevice" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_device_manager_get_device" clutter_device_manager_get_device :: 
    Ptr DeviceManager ->                    -- device_manager : TInterface (Name {namespace = "Clutter", name = "DeviceManager"})
    Int32 ->                                -- device_id : TBasicType TInt
    IO (Ptr Clutter.InputDevice.InputDevice)

-- | Retrieves the t'GI.Clutter.Objects.InputDevice.InputDevice' with the given /@deviceId@/
-- 
-- /Since: 1.2/
deviceManagerGetDevice ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceManager a) =>
    a
    -- ^ /@deviceManager@/: a t'GI.Clutter.Objects.DeviceManager.DeviceManager'
    -> Int32
    -- ^ /@deviceId@/: the integer id of a device
    -> m Clutter.InputDevice.InputDevice
    -- ^ __Returns:__ a t'GI.Clutter.Objects.InputDevice.InputDevice' or 'P.Nothing'. The
    --   returned device is owned by the t'GI.Clutter.Objects.DeviceManager.DeviceManager' and should
    --   never be modified or freed
deviceManagerGetDevice :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceManager a) =>
a -> Int32 -> m InputDevice
deviceManagerGetDevice a
deviceManager Int32
deviceId = IO InputDevice -> m InputDevice
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputDevice -> m InputDevice)
-> IO InputDevice -> m InputDevice
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceManager
deviceManager' <- a -> IO (Ptr DeviceManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
deviceManager
    Ptr InputDevice
result <- Ptr DeviceManager -> Int32 -> IO (Ptr InputDevice)
clutter_device_manager_get_device Ptr DeviceManager
deviceManager' Int32
deviceId
    Text -> Ptr InputDevice -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceManagerGetDevice" Ptr InputDevice
result
    InputDevice
result' <- ((ManagedPtr InputDevice -> InputDevice)
-> Ptr InputDevice -> IO InputDevice
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputDevice -> InputDevice
Clutter.InputDevice.InputDevice) Ptr InputDevice
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
deviceManager
    InputDevice -> IO InputDevice
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return InputDevice
result'

#if defined(ENABLE_OVERLOADING)
data DeviceManagerGetDeviceMethodInfo
instance (signature ~ (Int32 -> m Clutter.InputDevice.InputDevice), MonadIO m, IsDeviceManager a) => O.OverloadedMethod DeviceManagerGetDeviceMethodInfo a signature where
    overloadedMethod = deviceManagerGetDevice

instance O.OverloadedMethodInfo DeviceManagerGetDeviceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.DeviceManager.deviceManagerGetDevice",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeviceManager.html#v:deviceManagerGetDevice"
        })


#endif

-- method DeviceManager::list_devices
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device_manager"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "DeviceManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterDeviceManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGSList
--                  (TInterface Name { namespace = "Clutter" , name = "InputDevice" }))
-- throws : False
-- Skip return : False

foreign import ccall "clutter_device_manager_list_devices" clutter_device_manager_list_devices :: 
    Ptr DeviceManager ->                    -- device_manager : TInterface (Name {namespace = "Clutter", name = "DeviceManager"})
    IO (Ptr (GSList (Ptr Clutter.InputDevice.InputDevice)))

-- | Lists all currently registered input devices
-- 
-- /Since: 1.2/
deviceManagerListDevices ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceManager a) =>
    a
    -- ^ /@deviceManager@/: a t'GI.Clutter.Objects.DeviceManager.DeviceManager'
    -> m [Clutter.InputDevice.InputDevice]
    -- ^ __Returns:__ 
    --   a newly allocated list of t'GI.Clutter.Objects.InputDevice.InputDevice' objects. Use
    --   @/g_slist_free()/@ to deallocate it when done
deviceManagerListDevices :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceManager a) =>
a -> m [InputDevice]
deviceManagerListDevices a
deviceManager = IO [InputDevice] -> m [InputDevice]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [InputDevice] -> m [InputDevice])
-> IO [InputDevice] -> m [InputDevice]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceManager
deviceManager' <- a -> IO (Ptr DeviceManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
deviceManager
    Ptr (GSList (Ptr InputDevice))
result <- Ptr DeviceManager -> IO (Ptr (GSList (Ptr InputDevice)))
clutter_device_manager_list_devices Ptr DeviceManager
deviceManager'
    [Ptr InputDevice]
result' <- Ptr (GSList (Ptr InputDevice)) -> IO [Ptr InputDevice]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr InputDevice))
result
    [InputDevice]
result'' <- (Ptr InputDevice -> IO InputDevice)
-> [Ptr InputDevice] -> IO [InputDevice]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr InputDevice -> InputDevice)
-> Ptr InputDevice -> IO InputDevice
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputDevice -> InputDevice
Clutter.InputDevice.InputDevice) [Ptr InputDevice]
result'
    Ptr (GSList (Ptr InputDevice)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr InputDevice))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
deviceManager
    [InputDevice] -> IO [InputDevice]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [InputDevice]
result''

#if defined(ENABLE_OVERLOADING)
data DeviceManagerListDevicesMethodInfo
instance (signature ~ (m [Clutter.InputDevice.InputDevice]), MonadIO m, IsDeviceManager a) => O.OverloadedMethod DeviceManagerListDevicesMethodInfo a signature where
    overloadedMethod = deviceManagerListDevices

instance O.OverloadedMethodInfo DeviceManagerListDevicesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.DeviceManager.deviceManagerListDevices",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeviceManager.html#v:deviceManagerListDevices"
        })


#endif

-- method DeviceManager::peek_devices
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device_manager"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "DeviceManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterDeviceManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGSList
--                  (TInterface Name { namespace = "Clutter" , name = "InputDevice" }))
-- throws : False
-- Skip return : False

foreign import ccall "clutter_device_manager_peek_devices" clutter_device_manager_peek_devices :: 
    Ptr DeviceManager ->                    -- device_manager : TInterface (Name {namespace = "Clutter", name = "DeviceManager"})
    IO (Ptr (GSList (Ptr Clutter.InputDevice.InputDevice)))

-- | Lists all currently registered input devices
-- 
-- /Since: 1.2/
deviceManagerPeekDevices ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceManager a) =>
    a
    -- ^ /@deviceManager@/: a t'GI.Clutter.Objects.DeviceManager.DeviceManager'
    -> m [Clutter.InputDevice.InputDevice]
    -- ^ __Returns:__ 
    --   a pointer to the internal list of t'GI.Clutter.Objects.InputDevice.InputDevice' objects. The
    --   returned list is owned by the t'GI.Clutter.Objects.DeviceManager.DeviceManager' and should never
    --   be modified or freed
deviceManagerPeekDevices :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceManager a) =>
a -> m [InputDevice]
deviceManagerPeekDevices a
deviceManager = IO [InputDevice] -> m [InputDevice]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [InputDevice] -> m [InputDevice])
-> IO [InputDevice] -> m [InputDevice]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceManager
deviceManager' <- a -> IO (Ptr DeviceManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
deviceManager
    Ptr (GSList (Ptr InputDevice))
result <- Ptr DeviceManager -> IO (Ptr (GSList (Ptr InputDevice)))
clutter_device_manager_peek_devices Ptr DeviceManager
deviceManager'
    [Ptr InputDevice]
result' <- Ptr (GSList (Ptr InputDevice)) -> IO [Ptr InputDevice]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr InputDevice))
result
    [InputDevice]
result'' <- (Ptr InputDevice -> IO InputDevice)
-> [Ptr InputDevice] -> IO [InputDevice]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr InputDevice -> InputDevice)
-> Ptr InputDevice -> IO InputDevice
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputDevice -> InputDevice
Clutter.InputDevice.InputDevice) [Ptr InputDevice]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
deviceManager
    [InputDevice] -> IO [InputDevice]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [InputDevice]
result''

#if defined(ENABLE_OVERLOADING)
data DeviceManagerPeekDevicesMethodInfo
instance (signature ~ (m [Clutter.InputDevice.InputDevice]), MonadIO m, IsDeviceManager a) => O.OverloadedMethod DeviceManagerPeekDevicesMethodInfo a signature where
    overloadedMethod = deviceManagerPeekDevices

instance O.OverloadedMethodInfo DeviceManagerPeekDevicesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.DeviceManager.deviceManagerPeekDevices",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeviceManager.html#v:deviceManagerPeekDevices"
        })


#endif

-- method DeviceManager::get_default
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Clutter" , name = "DeviceManager" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_device_manager_get_default" clutter_device_manager_get_default :: 
    IO (Ptr DeviceManager)

-- | Retrieves the device manager singleton
-- 
-- /Since: 1.2/
deviceManagerGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m DeviceManager
    -- ^ __Returns:__ the t'GI.Clutter.Objects.DeviceManager.DeviceManager' singleton.
    --   The returned instance is owned by Clutter and it should not be
    --   modified or freed
deviceManagerGetDefault :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m DeviceManager
deviceManagerGetDefault  = IO DeviceManager -> m DeviceManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceManager -> m DeviceManager)
-> IO DeviceManager -> m DeviceManager
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceManager
result <- IO (Ptr DeviceManager)
clutter_device_manager_get_default
    Text -> Ptr DeviceManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceManagerGetDefault" Ptr DeviceManager
result
    DeviceManager
result' <- ((ManagedPtr DeviceManager -> DeviceManager)
-> Ptr DeviceManager -> IO DeviceManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DeviceManager -> DeviceManager
DeviceManager) Ptr DeviceManager
result
    DeviceManager -> IO DeviceManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DeviceManager
result'

#if defined(ENABLE_OVERLOADING)
#endif