{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gst.Objects.Device.Device' are objects representing a device, they contain
-- relevant metadata about the device, such as its class and the t'GI.Gst.Structs.Caps.Caps'
-- representing the media types it can produce or handle.
-- 
-- t'GI.Gst.Objects.Device.Device' are created by t'GI.Gst.Objects.DeviceProvider.DeviceProvider' objects which can be
-- aggregated by t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor' objects.
-- 
-- /Since: 1.4/

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

module GI.Gst.Objects.Device
    ( 

-- * Exported types
    Device(..)                              ,
    IsDevice                                ,
    toDevice                                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addControlBinding]("GI.Gst.Objects.Object#g:method:addControlBinding"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [createElement]("GI.Gst.Objects.Device#g:method:createElement"), [defaultError]("GI.Gst.Objects.Object#g:method:defaultError"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasActiveControlBindings]("GI.Gst.Objects.Object#g:method:hasActiveControlBindings"), [hasAncestor]("GI.Gst.Objects.Object#g:method:hasAncestor"), [hasAsAncestor]("GI.Gst.Objects.Object#g:method:hasAsAncestor"), [hasAsParent]("GI.Gst.Objects.Object#g:method:hasAsParent"), [hasClasses]("GI.Gst.Objects.Device#g:method:hasClasses"), [hasClassesv]("GI.Gst.Objects.Device#g:method:hasClassesv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [reconfigureElement]("GI.Gst.Objects.Device#g:method:reconfigureElement"), [ref]("GI.Gst.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeControlBinding]("GI.Gst.Objects.Object#g:method:removeControlBinding"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [suggestNextSync]("GI.Gst.Objects.Object#g:method:suggestNextSync"), [syncValues]("GI.Gst.Objects.Object#g:method:syncValues"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unparent]("GI.Gst.Objects.Object#g:method:unparent"), [unref]("GI.Gst.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCaps]("GI.Gst.Objects.Device#g:method:getCaps"), [getControlBinding]("GI.Gst.Objects.Object#g:method:getControlBinding"), [getControlRate]("GI.Gst.Objects.Object#g:method:getControlRate"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDeviceClass]("GI.Gst.Objects.Device#g:method:getDeviceClass"), [getDisplayName]("GI.Gst.Objects.Device#g:method:getDisplayName"), [getGValueArray]("GI.Gst.Objects.Object#g:method:getGValueArray"), [getName]("GI.Gst.Objects.Object#g:method:getName"), [getParent]("GI.Gst.Objects.Object#g:method:getParent"), [getPathString]("GI.Gst.Objects.Object#g:method:getPathString"), [getProperties]("GI.Gst.Objects.Device#g:method:getProperties"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getValue]("GI.Gst.Objects.Object#g:method:getValue").
-- 
-- ==== Setters
-- [setControlBindingDisabled]("GI.Gst.Objects.Object#g:method:setControlBindingDisabled"), [setControlBindingsDisabled]("GI.Gst.Objects.Object#g:method:setControlBindingsDisabled"), [setControlRate]("GI.Gst.Objects.Object#g:method:setControlRate"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setName]("GI.Gst.Objects.Object#g:method:setName"), [setParent]("GI.Gst.Objects.Object#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDeviceMethod                     ,
#endif

-- ** createElement #method:createElement#

#if defined(ENABLE_OVERLOADING)
    DeviceCreateElementMethodInfo           ,
#endif
    deviceCreateElement                     ,


-- ** getCaps #method:getCaps#

#if defined(ENABLE_OVERLOADING)
    DeviceGetCapsMethodInfo                 ,
#endif
    deviceGetCaps                           ,


-- ** getDeviceClass #method:getDeviceClass#

#if defined(ENABLE_OVERLOADING)
    DeviceGetDeviceClassMethodInfo          ,
#endif
    deviceGetDeviceClass                    ,


-- ** getDisplayName #method:getDisplayName#

#if defined(ENABLE_OVERLOADING)
    DeviceGetDisplayNameMethodInfo          ,
#endif
    deviceGetDisplayName                    ,


-- ** getProperties #method:getProperties#

#if defined(ENABLE_OVERLOADING)
    DeviceGetPropertiesMethodInfo           ,
#endif
    deviceGetProperties                     ,


-- ** hasClasses #method:hasClasses#

#if defined(ENABLE_OVERLOADING)
    DeviceHasClassesMethodInfo              ,
#endif
    deviceHasClasses                        ,


-- ** hasClassesv #method:hasClassesv#

#if defined(ENABLE_OVERLOADING)
    DeviceHasClassesvMethodInfo             ,
#endif
    deviceHasClassesv                       ,


-- ** reconfigureElement #method:reconfigureElement#

#if defined(ENABLE_OVERLOADING)
    DeviceReconfigureElementMethodInfo      ,
#endif
    deviceReconfigureElement                ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DeviceCapsPropertyInfo                  ,
#endif
    constructDeviceCaps                     ,
#if defined(ENABLE_OVERLOADING)
    deviceCaps                              ,
#endif
    getDeviceCaps                           ,


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

#if defined(ENABLE_OVERLOADING)
    DeviceDeviceClassPropertyInfo           ,
#endif
    constructDeviceDeviceClass              ,
#if defined(ENABLE_OVERLOADING)
    deviceDeviceClass                       ,
#endif
    getDeviceDeviceClass                    ,


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

#if defined(ENABLE_OVERLOADING)
    DeviceDisplayNamePropertyInfo           ,
#endif
    constructDeviceDisplayName              ,
#if defined(ENABLE_OVERLOADING)
    deviceDisplayName                       ,
#endif
    getDeviceDisplayName                    ,


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

#if defined(ENABLE_OVERLOADING)
    DevicePropertiesPropertyInfo            ,
#endif
    constructDeviceProperties               ,
#if defined(ENABLE_OVERLOADING)
    deviceProperties                        ,
#endif
    getDeviceProperties                     ,




 -- * Signals


-- ** removed #signal:removed#

    C_DeviceRemovedCallback                 ,
    DeviceRemovedCallback                   ,
#if defined(ENABLE_OVERLOADING)
    DeviceRemovedSignalInfo                 ,
#endif
    afterDeviceRemoved                      ,
    genClosure_DeviceRemoved                ,
    mk_DeviceRemovedCallback                ,
    noDeviceRemovedCallback                 ,
    onDeviceRemoved                         ,
    wrap_DeviceRemovedCallback              ,




    ) 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 {-# SOURCE #-} qualified GI.Gst.Objects.Element as Gst.Element
import {-# SOURCE #-} qualified GI.Gst.Objects.Object as Gst.Object
import {-# SOURCE #-} qualified GI.Gst.Structs.Caps as Gst.Caps
import {-# SOURCE #-} qualified GI.Gst.Structs.Structure as Gst.Structure

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

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

foreign import ccall "gst_device_get_type"
    c_gst_device_get_type :: IO B.Types.GType

instance B.Types.TypedObject Device where
    glibType :: IO GType
glibType = IO GType
c_gst_device_get_type

instance B.Types.GObject Device

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

instance O.HasParentTypes Device
type instance O.ParentTypes Device = '[Gst.Object.Object, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceMethod (t :: Symbol) (o :: *) :: * where
    ResolveDeviceMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
    ResolveDeviceMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDeviceMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDeviceMethod "createElement" o = DeviceCreateElementMethodInfo
    ResolveDeviceMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
    ResolveDeviceMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDeviceMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDeviceMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDeviceMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
    ResolveDeviceMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
    ResolveDeviceMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
    ResolveDeviceMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
    ResolveDeviceMethod "hasClasses" o = DeviceHasClassesMethodInfo
    ResolveDeviceMethod "hasClassesv" o = DeviceHasClassesvMethodInfo
    ResolveDeviceMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDeviceMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDeviceMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDeviceMethod "reconfigureElement" o = DeviceReconfigureElementMethodInfo
    ResolveDeviceMethod "ref" o = Gst.Object.ObjectRefMethodInfo
    ResolveDeviceMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDeviceMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
    ResolveDeviceMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDeviceMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDeviceMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDeviceMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
    ResolveDeviceMethod "syncValues" o = Gst.Object.ObjectSyncValuesMethodInfo
    ResolveDeviceMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDeviceMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
    ResolveDeviceMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
    ResolveDeviceMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDeviceMethod "getCaps" o = DeviceGetCapsMethodInfo
    ResolveDeviceMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
    ResolveDeviceMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
    ResolveDeviceMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDeviceMethod "getDeviceClass" o = DeviceGetDeviceClassMethodInfo
    ResolveDeviceMethod "getDisplayName" o = DeviceGetDisplayNameMethodInfo
    ResolveDeviceMethod "getGValueArray" o = Gst.Object.ObjectGetGValueArrayMethodInfo
    ResolveDeviceMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
    ResolveDeviceMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
    ResolveDeviceMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
    ResolveDeviceMethod "getProperties" o = DeviceGetPropertiesMethodInfo
    ResolveDeviceMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDeviceMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDeviceMethod "getValue" o = Gst.Object.ObjectGetValueMethodInfo
    ResolveDeviceMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
    ResolveDeviceMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
    ResolveDeviceMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
    ResolveDeviceMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDeviceMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDeviceMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
    ResolveDeviceMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
    ResolveDeviceMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDeviceMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal Device::removed
-- | /No description available in the introspection data./
type DeviceRemovedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DeviceRemovedCallback`@.
noDeviceRemovedCallback :: Maybe DeviceRemovedCallback
noDeviceRemovedCallback :: Maybe (IO ())
noDeviceRemovedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DeviceRemovedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_DeviceRemoved :: MonadIO m => DeviceRemovedCallback -> m (GClosure C_DeviceRemovedCallback)
genClosure_DeviceRemoved :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_DeviceRemovedCallback)
genClosure_DeviceRemoved IO ()
cb = IO (GClosure C_DeviceRemovedCallback)
-> m (GClosure C_DeviceRemovedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DeviceRemovedCallback)
 -> m (GClosure C_DeviceRemovedCallback))
-> IO (GClosure C_DeviceRemovedCallback)
-> m (GClosure C_DeviceRemovedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DeviceRemovedCallback
cb' = IO () -> C_DeviceRemovedCallback
wrap_DeviceRemovedCallback IO ()
cb
    C_DeviceRemovedCallback -> IO (FunPtr C_DeviceRemovedCallback)
mk_DeviceRemovedCallback C_DeviceRemovedCallback
cb' IO (FunPtr C_DeviceRemovedCallback)
-> (FunPtr C_DeviceRemovedCallback
    -> IO (GClosure C_DeviceRemovedCallback))
-> IO (GClosure C_DeviceRemovedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DeviceRemovedCallback
-> IO (GClosure C_DeviceRemovedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DeviceRemovedCallback` into a `C_DeviceRemovedCallback`.
wrap_DeviceRemovedCallback ::
    DeviceRemovedCallback ->
    C_DeviceRemovedCallback
wrap_DeviceRemovedCallback :: IO () -> C_DeviceRemovedCallback
wrap_DeviceRemovedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [removed](#signal:removed) 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' device #removed callback
-- @
-- 
-- 
onDeviceRemoved :: (IsDevice a, MonadIO m) => a -> DeviceRemovedCallback -> m SignalHandlerId
onDeviceRemoved :: forall a (m :: * -> *).
(IsDevice a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onDeviceRemoved a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_DeviceRemovedCallback
cb' = IO () -> C_DeviceRemovedCallback
wrap_DeviceRemovedCallback IO ()
cb
    FunPtr C_DeviceRemovedCallback
cb'' <- C_DeviceRemovedCallback -> IO (FunPtr C_DeviceRemovedCallback)
mk_DeviceRemovedCallback C_DeviceRemovedCallback
cb'
    a
-> Text
-> FunPtr C_DeviceRemovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"removed" FunPtr C_DeviceRemovedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [removed](#signal:removed) 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' device #removed callback
-- @
-- 
-- 
afterDeviceRemoved :: (IsDevice a, MonadIO m) => a -> DeviceRemovedCallback -> m SignalHandlerId
afterDeviceRemoved :: forall a (m :: * -> *).
(IsDevice a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterDeviceRemoved a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_DeviceRemovedCallback
cb' = IO () -> C_DeviceRemovedCallback
wrap_DeviceRemovedCallback IO ()
cb
    FunPtr C_DeviceRemovedCallback
cb'' <- C_DeviceRemovedCallback -> IO (FunPtr C_DeviceRemovedCallback)
mk_DeviceRemovedCallback C_DeviceRemovedCallback
cb'
    a
-> Text
-> FunPtr C_DeviceRemovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"removed" FunPtr C_DeviceRemovedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DeviceRemovedSignalInfo
instance SignalInfo DeviceRemovedSignalInfo where
    type HaskellCallbackType DeviceRemovedSignalInfo = DeviceRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DeviceRemovedCallback cb
        cb'' <- mk_DeviceRemovedCallback cb'
        connectSignalFunPtr obj "removed" cb'' connectMode detail

#endif

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

-- | Get the value of the “@caps@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #caps
-- @
getDeviceCaps :: (MonadIO m, IsDevice o) => o -> m (Maybe Gst.Caps.Caps)
getDeviceCaps :: forall (m :: * -> *) o.
(MonadIO m, IsDevice o) =>
o -> m (Maybe Caps)
getDeviceCaps o
obj = IO (Maybe Caps) -> m (Maybe Caps)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Caps) -> m (Maybe Caps))
-> IO (Maybe Caps) -> m (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Caps -> Caps) -> IO (Maybe Caps)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"caps" ManagedPtr Caps -> Caps
Gst.Caps.Caps

-- | Construct a `GValueConstruct` with valid value for the “@caps@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceCaps :: (IsDevice o, MIO.MonadIO m) => Gst.Caps.Caps -> m (GValueConstruct o)
constructDeviceCaps :: forall o (m :: * -> *).
(IsDevice o, MonadIO m) =>
Caps -> m (GValueConstruct o)
constructDeviceCaps Caps
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 Caps -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"caps" (Caps -> Maybe Caps
forall a. a -> Maybe a
P.Just Caps
val)

#if defined(ENABLE_OVERLOADING)
data DeviceCapsPropertyInfo
instance AttrInfo DeviceCapsPropertyInfo where
    type AttrAllowedOps DeviceCapsPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceCapsPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceCapsPropertyInfo = (~) Gst.Caps.Caps
    type AttrTransferTypeConstraint DeviceCapsPropertyInfo = (~) Gst.Caps.Caps
    type AttrTransferType DeviceCapsPropertyInfo = Gst.Caps.Caps
    type AttrGetType DeviceCapsPropertyInfo = (Maybe Gst.Caps.Caps)
    type AttrLabel DeviceCapsPropertyInfo = "caps"
    type AttrOrigin DeviceCapsPropertyInfo = Device
    attrGet = getDeviceCaps
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceCaps
    attrClear = undefined
#endif

-- VVV Prop "device-class"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@device-class@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #deviceClass
-- @
getDeviceDeviceClass :: (MonadIO m, IsDevice o) => o -> m (Maybe T.Text)
getDeviceDeviceClass :: forall (m :: * -> *) o.
(MonadIO m, IsDevice o) =>
o -> m (Maybe Text)
getDeviceDeviceClass o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"device-class"

-- | Construct a `GValueConstruct` with valid value for the “@device-class@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceDeviceClass :: (IsDevice o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDeviceDeviceClass :: forall o (m :: * -> *).
(IsDevice o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDeviceDeviceClass Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"device-class" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DeviceDeviceClassPropertyInfo
instance AttrInfo DeviceDeviceClassPropertyInfo where
    type AttrAllowedOps DeviceDeviceClassPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceDeviceClassPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceDeviceClassPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DeviceDeviceClassPropertyInfo = (~) T.Text
    type AttrTransferType DeviceDeviceClassPropertyInfo = T.Text
    type AttrGetType DeviceDeviceClassPropertyInfo = (Maybe T.Text)
    type AttrLabel DeviceDeviceClassPropertyInfo = "device-class"
    type AttrOrigin DeviceDeviceClassPropertyInfo = Device
    attrGet = getDeviceDeviceClass
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceDeviceClass
    attrClear = undefined
#endif

-- VVV Prop "display-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@display-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #displayName
-- @
getDeviceDisplayName :: (MonadIO m, IsDevice o) => o -> m (Maybe T.Text)
getDeviceDisplayName :: forall (m :: * -> *) o.
(MonadIO m, IsDevice o) =>
o -> m (Maybe Text)
getDeviceDisplayName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"display-name"

-- | Construct a `GValueConstruct` with valid value for the “@display-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceDisplayName :: (IsDevice o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDeviceDisplayName :: forall o (m :: * -> *).
(IsDevice o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDeviceDisplayName Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"display-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DeviceDisplayNamePropertyInfo
instance AttrInfo DeviceDisplayNamePropertyInfo where
    type AttrAllowedOps DeviceDisplayNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceDisplayNamePropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceDisplayNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DeviceDisplayNamePropertyInfo = (~) T.Text
    type AttrTransferType DeviceDisplayNamePropertyInfo = T.Text
    type AttrGetType DeviceDisplayNamePropertyInfo = (Maybe T.Text)
    type AttrLabel DeviceDisplayNamePropertyInfo = "display-name"
    type AttrOrigin DeviceDisplayNamePropertyInfo = Device
    attrGet = getDeviceDisplayName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceDisplayName
    attrClear = undefined
#endif

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

-- | Get the value of the “@properties@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #properties
-- @
getDeviceProperties :: (MonadIO m, IsDevice o) => o -> m (Maybe Gst.Structure.Structure)
getDeviceProperties :: forall (m :: * -> *) o.
(MonadIO m, IsDevice o) =>
o -> m (Maybe Structure)
getDeviceProperties o
obj = IO (Maybe Structure) -> m (Maybe Structure)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Structure) -> m (Maybe Structure))
-> IO (Maybe Structure) -> m (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Structure -> Structure)
-> IO (Maybe Structure)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"properties" ManagedPtr Structure -> Structure
Gst.Structure.Structure

-- | Construct a `GValueConstruct` with valid value for the “@properties@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceProperties :: (IsDevice o, MIO.MonadIO m) => Gst.Structure.Structure -> m (GValueConstruct o)
constructDeviceProperties :: forall o (m :: * -> *).
(IsDevice o, MonadIO m) =>
Structure -> m (GValueConstruct o)
constructDeviceProperties Structure
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 Structure -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"properties" (Structure -> Maybe Structure
forall a. a -> Maybe a
P.Just Structure
val)

#if defined(ENABLE_OVERLOADING)
data DevicePropertiesPropertyInfo
instance AttrInfo DevicePropertiesPropertyInfo where
    type AttrAllowedOps DevicePropertiesPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DevicePropertiesPropertyInfo = IsDevice
    type AttrSetTypeConstraint DevicePropertiesPropertyInfo = (~) Gst.Structure.Structure
    type AttrTransferTypeConstraint DevicePropertiesPropertyInfo = (~) Gst.Structure.Structure
    type AttrTransferType DevicePropertiesPropertyInfo = Gst.Structure.Structure
    type AttrGetType DevicePropertiesPropertyInfo = (Maybe Gst.Structure.Structure)
    type AttrLabel DevicePropertiesPropertyInfo = "properties"
    type AttrOrigin DevicePropertiesPropertyInfo = Device
    attrGet = getDeviceProperties
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceProperties
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Device
type instance O.AttributeList Device = DeviceAttributeList
type DeviceAttributeList = ('[ '("caps", DeviceCapsPropertyInfo), '("deviceClass", DeviceDeviceClassPropertyInfo), '("displayName", DeviceDisplayNamePropertyInfo), '("name", Gst.Object.ObjectNamePropertyInfo), '("parent", Gst.Object.ObjectParentPropertyInfo), '("properties", DevicePropertiesPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
deviceCaps :: AttrLabelProxy "caps"
deviceCaps = AttrLabelProxy

deviceDeviceClass :: AttrLabelProxy "deviceClass"
deviceDeviceClass = AttrLabelProxy

deviceDisplayName :: AttrLabelProxy "displayName"
deviceDisplayName = AttrLabelProxy

deviceProperties :: AttrLabelProxy "properties"
deviceProperties = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Device = DeviceSignalList
type DeviceSignalList = ('[ '("deepNotify", Gst.Object.ObjectDeepNotifySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("removed", DeviceRemovedSignalInfo)] :: [(Symbol, *)])

#endif

-- method Device::create_element
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gst" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "name of new element, or %NULL to automatically\ncreate a unique name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Element" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_create_element" gst_device_create_element :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gst", name = "Device"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr Gst.Element.Element)

-- | Creates the element with all of the required parameters set to use
-- this device.
-- 
-- /Since: 1.4/
deviceCreateElement ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gst.Objects.Device.Device'
    -> Maybe (T.Text)
    -- ^ /@name@/: name of new element, or 'P.Nothing' to automatically
    -- create a unique name.
    -> m (Maybe Gst.Element.Element)
    -- ^ __Returns:__ a new t'GI.Gst.Objects.Element.Element' configured to use
    -- this device
deviceCreateElement :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> Maybe Text -> m (Maybe Element)
deviceCreateElement a
device Maybe Text
name = IO (Maybe Element) -> m (Maybe Element)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Element) -> m (Maybe Element))
-> IO (Maybe Element) -> m (Maybe Element)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr CChar
maybeName <- case Maybe Text
name of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jName -> do
            Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
    Ptr Element
result <- Ptr Device -> Ptr CChar -> IO (Ptr Element)
gst_device_create_element Ptr Device
device' Ptr CChar
maybeName
    Maybe Element
maybeResult <- Ptr Element -> (Ptr Element -> IO Element) -> IO (Maybe Element)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Element
result ((Ptr Element -> IO Element) -> IO (Maybe Element))
-> (Ptr Element -> IO Element) -> IO (Maybe Element)
forall a b. (a -> b) -> a -> b
$ \Ptr Element
result' -> do
        Element
result'' <- ((ManagedPtr Element -> Element) -> Ptr Element -> IO Element
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Element -> Element
Gst.Element.Element) Ptr Element
result'
        Element -> IO Element
forall (m :: * -> *) a. Monad m => a -> m a
return Element
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
    Maybe Element -> IO (Maybe Element)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Element
maybeResult

#if defined(ENABLE_OVERLOADING)
data DeviceCreateElementMethodInfo
instance (signature ~ (Maybe (T.Text) -> m (Maybe Gst.Element.Element)), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceCreateElementMethodInfo a signature where
    overloadedMethod = deviceCreateElement

instance O.OverloadedMethodInfo DeviceCreateElementMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.Device.deviceCreateElement",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-Device.html#v:deviceCreateElement"
        }


#endif

-- method Device::get_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gst" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Caps" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_get_caps" gst_device_get_caps :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gst", name = "Device"})
    IO (Ptr Gst.Caps.Caps)

-- | Getter for the t'GI.Gst.Structs.Caps.Caps' that this device supports.
-- 
-- /Since: 1.4/
deviceGetCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gst.Objects.Device.Device'
    -> m (Maybe Gst.Caps.Caps)
    -- ^ __Returns:__ The t'GI.Gst.Structs.Caps.Caps' supported by this device. Unref with
    -- @/gst_caps_unref()/@ when done.
deviceGetCaps :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> m (Maybe Caps)
deviceGetCaps a
device = IO (Maybe Caps) -> m (Maybe Caps)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Caps) -> m (Maybe Caps))
-> IO (Maybe Caps) -> m (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Caps
result <- Ptr Device -> IO (Ptr Caps)
gst_device_get_caps Ptr Device
device'
    Maybe Caps
maybeResult <- Ptr Caps -> (Ptr Caps -> IO Caps) -> IO (Maybe Caps)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Caps
result ((Ptr Caps -> IO Caps) -> IO (Maybe Caps))
-> (Ptr Caps -> IO Caps) -> IO (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ \Ptr Caps
result' -> do
        Caps
result'' <- ((ManagedPtr Caps -> Caps) -> Ptr Caps -> IO Caps
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Caps -> Caps
Gst.Caps.Caps) Ptr Caps
result'
        Caps -> IO Caps
forall (m :: * -> *) a. Monad m => a -> m a
return Caps
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Maybe Caps -> IO (Maybe Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Caps
maybeResult

#if defined(ENABLE_OVERLOADING)
data DeviceGetCapsMethodInfo
instance (signature ~ (m (Maybe Gst.Caps.Caps)), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceGetCapsMethodInfo a signature where
    overloadedMethod = deviceGetCaps

instance O.OverloadedMethodInfo DeviceGetCapsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.Device.deviceGetCaps",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-Device.html#v:deviceGetCaps"
        }


#endif

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

foreign import ccall "gst_device_get_device_class" gst_device_get_device_class :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gst", name = "Device"})
    IO CString

-- | Gets the \"class\" of a device. This is a \"\/\" separated list of
-- classes that represent this device. They are a subset of the
-- classes of the t'GI.Gst.Objects.DeviceProvider.DeviceProvider' that produced this device.
-- 
-- /Since: 1.4/
deviceGetDeviceClass ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gst.Objects.Device.Device'
    -> m T.Text
    -- ^ __Returns:__ The device class. Free with 'GI.GLib.Functions.free' after use.
deviceGetDeviceClass :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> m Text
deviceGetDeviceClass a
device = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr CChar
result <- Ptr Device -> IO (Ptr CChar)
gst_device_get_device_class Ptr Device
device'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceGetDeviceClass" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetDeviceClassMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceGetDeviceClassMethodInfo a signature where
    overloadedMethod = deviceGetDeviceClass

instance O.OverloadedMethodInfo DeviceGetDeviceClassMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.Device.deviceGetDeviceClass",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-Device.html#v:deviceGetDeviceClass"
        }


#endif

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

foreign import ccall "gst_device_get_display_name" gst_device_get_display_name :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gst", name = "Device"})
    IO CString

-- | Gets the user-friendly name of the device.
-- 
-- /Since: 1.4/
deviceGetDisplayName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gst.Objects.Device.Device'
    -> m T.Text
    -- ^ __Returns:__ The device name. Free with 'GI.GLib.Functions.free' after use.
deviceGetDisplayName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> m Text
deviceGetDisplayName a
device = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr CChar
result <- Ptr Device -> IO (Ptr CChar)
gst_device_get_display_name Ptr Device
device'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceGetDisplayName" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetDisplayNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceGetDisplayNameMethodInfo a signature where
    overloadedMethod = deviceGetDisplayName

instance O.OverloadedMethodInfo DeviceGetDisplayNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.Device.deviceGetDisplayName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-Device.html#v:deviceGetDisplayName"
        }


#endif

-- method Device::get_properties
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gst" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Structure" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_get_properties" gst_device_get_properties :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gst", name = "Device"})
    IO (Ptr Gst.Structure.Structure)

-- | Gets the extra properties of a device.
-- 
-- /Since: 1.6/
deviceGetProperties ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gst.Objects.Device.Device'
    -> m (Maybe Gst.Structure.Structure)
    -- ^ __Returns:__ The extra properties or 'P.Nothing' when there are none.
    --          Free with 'GI.Gst.Structs.Structure.structureFree' after use.
deviceGetProperties :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> m (Maybe Structure)
deviceGetProperties a
device = IO (Maybe Structure) -> m (Maybe Structure)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Structure) -> m (Maybe Structure))
-> IO (Maybe Structure) -> m (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Structure
result <- Ptr Device -> IO (Ptr Structure)
gst_device_get_properties Ptr Device
device'
    Maybe Structure
maybeResult <- Ptr Structure
-> (Ptr Structure -> IO Structure) -> IO (Maybe Structure)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Structure
result ((Ptr Structure -> IO Structure) -> IO (Maybe Structure))
-> (Ptr Structure -> IO Structure) -> IO (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ \Ptr Structure
result' -> do
        Structure
result'' <- ((ManagedPtr Structure -> Structure)
-> Ptr Structure -> IO Structure
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Structure -> Structure
Gst.Structure.Structure) Ptr Structure
result'
        Structure -> IO Structure
forall (m :: * -> *) a. Monad m => a -> m a
return Structure
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Maybe Structure -> IO (Maybe Structure)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Structure
maybeResult

#if defined(ENABLE_OVERLOADING)
data DeviceGetPropertiesMethodInfo
instance (signature ~ (m (Maybe Gst.Structure.Structure)), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceGetPropertiesMethodInfo a signature where
    overloadedMethod = deviceGetProperties

instance O.OverloadedMethodInfo DeviceGetPropertiesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.Device.deviceGetProperties",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-Device.html#v:deviceGetProperties"
        }


#endif

-- method Device::has_classes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gst" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "classes"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a \"/\"-separated list of device classes to match, only match if\n all classes are matched"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_has_classes" gst_device_has_classes :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gst", name = "Device"})
    CString ->                              -- classes : TBasicType TUTF8
    IO CInt

-- | Check if /@device@/ matches all of the given classes
-- 
-- /Since: 1.4/
deviceHasClasses ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gst.Objects.Device.Device'
    -> T.Text
    -- ^ /@classes@/: a \"\/\"-separated list of device classes to match, only match if
    --  all classes are matched
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@device@/ matches.
deviceHasClasses :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> Text -> m Bool
deviceHasClasses a
device Text
classes = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr CChar
classes' <- Text -> IO (Ptr CChar)
textToCString Text
classes
    CInt
result <- Ptr Device -> Ptr CChar -> IO CInt
gst_device_has_classes Ptr Device
device' Ptr CChar
classes'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
classes'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DeviceHasClassesMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceHasClassesMethodInfo a signature where
    overloadedMethod = deviceHasClasses

instance O.OverloadedMethodInfo DeviceHasClassesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.Device.deviceHasClasses",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-Device.html#v:deviceHasClasses"
        }


#endif

-- method Device::has_classesv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gst" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "classes"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a %NULL terminated array of classes\n  to match, only match if all classes are matched"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_has_classesv" gst_device_has_classesv :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gst", name = "Device"})
    Ptr CString ->                          -- classes : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO CInt

-- | Check if /@factory@/ matches all of the given classes
-- 
-- /Since: 1.4/
deviceHasClassesv ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gst.Objects.Device.Device'
    -> [T.Text]
    -- ^ /@classes@/: a 'P.Nothing' terminated array of classes
    --   to match, only match if all classes are matched
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@device@/ matches.
deviceHasClassesv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> [Text] -> m Bool
deviceHasClassesv a
device [Text]
classes = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr (Ptr CChar)
classes' <- [Text] -> IO (Ptr (Ptr CChar))
packZeroTerminatedUTF8CArray [Text]
classes
    CInt
result <- Ptr Device -> Ptr (Ptr CChar) -> IO CInt
gst_device_has_classesv Ptr Device
device' Ptr (Ptr CChar)
classes'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    (Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
classes'
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
classes'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DeviceHasClassesvMethodInfo
instance (signature ~ ([T.Text] -> m Bool), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceHasClassesvMethodInfo a signature where
    overloadedMethod = deviceHasClassesv

instance O.OverloadedMethodInfo DeviceHasClassesvMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.Device.deviceHasClassesv",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-Device.html#v:deviceHasClassesv"
        }


#endif

-- method Device::reconfigure_element
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gst" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "element"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "Element" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstElement" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_reconfigure_element" gst_device_reconfigure_element :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gst", name = "Device"})
    Ptr Gst.Element.Element ->              -- element : TInterface (Name {namespace = "Gst", name = "Element"})
    IO CInt

-- | Tries to reconfigure an existing element to use the device. If this
-- function fails, then one must destroy the element and create a new one
-- using 'GI.Gst.Objects.Device.deviceCreateElement'.
-- 
-- Note: This should only be implemented for elements can change their
-- device in the PLAYING state.
-- 
-- /Since: 1.4/
deviceReconfigureElement ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a, Gst.Element.IsElement b) =>
    a
    -- ^ /@device@/: a t'GI.Gst.Objects.Device.Device'
    -> b
    -- ^ /@element@/: a t'GI.Gst.Objects.Element.Element'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the element could be reconfigured to use this device,
    -- 'P.False' otherwise.
deviceReconfigureElement :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDevice a, IsElement b) =>
a -> b -> m Bool
deviceReconfigureElement a
device b
element = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Element
element' <- b -> IO (Ptr Element)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
element
    CInt
result <- Ptr Device -> Ptr Element -> IO CInt
gst_device_reconfigure_element Ptr Device
device' Ptr Element
element'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
element
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DeviceReconfigureElementMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDevice a, Gst.Element.IsElement b) => O.OverloadedMethod DeviceReconfigureElementMethodInfo a signature where
    overloadedMethod = deviceReconfigureElement

instance O.OverloadedMethodInfo DeviceReconfigureElementMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gst.Objects.Device.deviceReconfigureElement",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gst-1.0.24/docs/GI-Gst-Objects-Device.html#v:deviceReconfigureElement"
        }


#endif