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


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

#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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# 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 (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)
foreign import ccall "gst_device_get_type"
    c_gst_device_get_type :: IO GType

instance GObject Device where
    gobjectType :: IO GType
gobjectType = IO GType
c_gst_device_get_type
    

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

-- | Type class for types which can be safely cast to `Device`, for instance with `toDevice`.
class (GObject o, O.IsDescendantOf Device o) => IsDevice o
instance (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 :: (MonadIO m, IsDevice o) => o -> m Device
toDevice :: o -> m Device
toDevice = IO Device -> m Device
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Device -> Device
Device

-- | A convenience alias for `Nothing` :: `Maybe` `Device`.
noDevice :: Maybe Device
noDevice :: Maybe Device
noDevice = Maybe Device
forall a. Maybe a
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.MethodInfo 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

#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 :: IO () -> m (GClosure C_DeviceRemovedCallback)
genClosure_DeviceRemoved cb :: 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 _cb :: IO ()
_cb _ _ = 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 :: a -> IO () -> m SignalHandlerId
onDeviceRemoved obj :: a
obj cb :: 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 "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 :: a -> IO () -> m SignalHandlerId
afterDeviceRemoved obj :: a
obj cb :: 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 "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 :: o -> m (Maybe Caps)
getDeviceCaps obj :: o
obj = 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
$ o -> String -> (ManagedPtr Caps -> Caps) -> IO (Maybe Caps)
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj "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) => Gst.Caps.Caps -> IO (GValueConstruct o)
constructDeviceCaps :: Caps -> IO (GValueConstruct o)
constructDeviceCaps val :: Caps
val = String -> Maybe Caps -> IO (GValueConstruct o)
forall a o.
BoxedObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed "caps" (Caps -> Maybe Caps
forall a. a -> Maybe a
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 :: o -> m (Maybe Text)
getDeviceDeviceClass obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "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) => T.Text -> IO (GValueConstruct o)
constructDeviceDeviceClass :: Text -> IO (GValueConstruct o)
constructDeviceDeviceClass val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "device-class" (Text -> Maybe Text
forall a. a -> Maybe a
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 :: o -> m (Maybe Text)
getDeviceDisplayName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "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) => T.Text -> IO (GValueConstruct o)
constructDeviceDisplayName :: Text -> IO (GValueConstruct o)
constructDeviceDisplayName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "display-name" (Text -> Maybe Text
forall a. a -> Maybe a
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 :: o -> m (Maybe Structure)
getDeviceProperties obj :: o
obj = 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
$ o
-> String
-> (ManagedPtr Structure -> Structure)
-> IO (Maybe Structure)
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj "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) => Gst.Structure.Structure -> IO (GValueConstruct o)
constructDeviceProperties :: Structure -> IO (GValueConstruct o)
constructDeviceProperties val :: Structure
val = String -> Maybe Structure -> IO (GValueConstruct o)
forall a o.
BoxedObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed "properties" (Structure -> Maybe Structure
forall a. a -> Maybe a
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 :: a -> Maybe Text -> m (Maybe Element)
deviceCreateElement device :: a
device name :: 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
        Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just jName :: 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
$ \result' :: 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
wrapObject 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.MethodInfo DeviceCreateElementMethodInfo a signature where
    overloadedMethod = 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 :: a -> m (Maybe Caps)
deviceGetCaps device :: 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
$ \result' :: Ptr Caps
result' -> do
        Caps
result'' <- ((ManagedPtr Caps -> Caps) -> Ptr Caps -> IO Caps
forall a.
(HasCallStack, BoxedObject 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.MethodInfo DeviceGetCapsMethodInfo a signature where
    overloadedMethod = 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 :: a -> m Text
deviceGetDeviceClass device :: 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 "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.MethodInfo DeviceGetDeviceClassMethodInfo a signature where
    overloadedMethod = 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 :: a -> m Text
deviceGetDisplayName device :: 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 "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.MethodInfo DeviceGetDisplayNameMethodInfo a signature where
    overloadedMethod = 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 :: a -> m (Maybe Structure)
deviceGetProperties device :: 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
$ \result' :: Ptr Structure
result' -> do
        Structure
result'' <- ((ManagedPtr Structure -> Structure)
-> Ptr Structure -> IO Structure
forall a.
(HasCallStack, BoxedObject 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.MethodInfo DeviceGetPropertiesMethodInfo a signature where
    overloadedMethod = 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 :: a -> Text -> m Bool
deviceHasClasses device :: a
device classes :: 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
/= 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.MethodInfo DeviceHasClassesMethodInfo a signature where
    overloadedMethod = 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 :: a -> [Text] -> m Bool
deviceHasClassesv device :: a
device classes :: [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
/= 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.MethodInfo DeviceHasClassesvMethodInfo a signature where
    overloadedMethod = 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 :: a -> b -> m Bool
deviceReconfigureElement device :: a
device element :: 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
/= 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.MethodInfo DeviceReconfigureElementMethodInfo a signature where
    overloadedMethod = deviceReconfigureElement

#endif