{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Applications should create a t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor' when they want
-- to probe, list and monitor devices of a specific type. The
-- t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor' will create the appropriate
-- t'GI.Gst.Objects.DeviceProvider.DeviceProvider' objects and manage them. It will then post
-- messages on its t'GI.Gst.Objects.Bus.Bus' for devices that have been added and
-- removed.
-- 
-- The device monitor will monitor all devices matching the filters that
-- the application has set.
-- 
-- The basic use pattern of a device monitor is as follows:
-- >
-- >  static gboolean
-- >  my_bus_func (GstBus * bus, GstMessage * message, gpointer user_data)
-- >  {
-- >     GstDevice *device;
-- >     gchar *name;
-- >
-- >     switch (GST_MESSAGE_TYPE (message)) {
-- >       case GST_MESSAGE_DEVICE_ADDED:
-- >         gst_message_parse_device_added (message, &device);
-- >         name = gst_device_get_display_name (device);
-- >         g_print("Device added: %s\n", name);
-- >         g_free (name);
-- >         gst_object_unref (device);
-- >         break;
-- >       case GST_MESSAGE_DEVICE_REMOVED:
-- >         gst_message_parse_device_removed (message, &device);
-- >         name = gst_device_get_display_name (device);
-- >         g_print("Device removed: %s\n", name);
-- >         g_free (name);
-- >         gst_object_unref (device);
-- >         break;
-- >       default:
-- >         break;
-- >     }
-- >
-- >     return G_SOURCE_CONTINUE;
-- >  }
-- >
-- >  GstDeviceMonitor *
-- >  setup_raw_video_source_device_monitor (void) {
-- >     GstDeviceMonitor *monitor;
-- >     GstBus *bus;
-- >     GstCaps *caps;
-- >
-- >     monitor = gst_device_monitor_new ();
-- >
-- >     bus = gst_device_monitor_get_bus (monitor);
-- >     gst_bus_add_watch (bus, my_bus_func, NULL);
-- >     gst_object_unref (bus);
-- >
-- >     caps = gst_caps_new_empty_simple ("video/x-raw");
-- >     gst_device_monitor_add_filter (monitor, "Video/Source", caps);
-- >     gst_caps_unref (caps);
-- >
-- >     gst_device_monitor_start (monitor);
-- >
-- >     return monitor;
-- >  }
-- 
-- 
-- /Since: 1.4/

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

module GI.Gst.Objects.DeviceMonitor
    ( 

-- * Exported types
    DeviceMonitor(..)                       ,
    IsDeviceMonitor                         ,
    toDeviceMonitor                         ,
    noDeviceMonitor                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDeviceMonitorMethod              ,
#endif


-- ** addFilter #method:addFilter#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorAddFilterMethodInfo        ,
#endif
    deviceMonitorAddFilter                  ,


-- ** getBus #method:getBus#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorGetBusMethodInfo           ,
#endif
    deviceMonitorGetBus                     ,


-- ** getDevices #method:getDevices#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorGetDevicesMethodInfo       ,
#endif
    deviceMonitorGetDevices                 ,


-- ** getProviders #method:getProviders#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorGetProvidersMethodInfo     ,
#endif
    deviceMonitorGetProviders               ,


-- ** getShowAllDevices #method:getShowAllDevices#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorGetShowAllDevicesMethodInfo,
#endif
    deviceMonitorGetShowAllDevices          ,


-- ** new #method:new#

    deviceMonitorNew                        ,


-- ** removeFilter #method:removeFilter#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorRemoveFilterMethodInfo     ,
#endif
    deviceMonitorRemoveFilter               ,


-- ** setShowAllDevices #method:setShowAllDevices#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorSetShowAllDevicesMethodInfo,
#endif
    deviceMonitorSetShowAllDevices          ,


-- ** start #method:start#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorStartMethodInfo            ,
#endif
    deviceMonitorStart                      ,


-- ** stop #method:stop#

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorStopMethodInfo             ,
#endif
    deviceMonitorStop                       ,




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

#if defined(ENABLE_OVERLOADING)
    DeviceMonitorShowAllPropertyInfo        ,
#endif
    constructDeviceMonitorShowAll           ,
#if defined(ENABLE_OVERLOADING)
    deviceMonitorShowAll                    ,
#endif
    getDeviceMonitorShowAll                 ,
    setDeviceMonitorShowAll                 ,




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

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

instance GObject DeviceMonitor where
    gobjectType :: IO GType
gobjectType = IO GType
c_gst_device_monitor_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `DeviceMonitor`.
noDeviceMonitor :: Maybe DeviceMonitor
noDeviceMonitor :: Maybe DeviceMonitor
noDeviceMonitor = Maybe DeviceMonitor
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceMonitorMethod (t :: Symbol) (o :: *) :: * where
    ResolveDeviceMonitorMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
    ResolveDeviceMonitorMethod "addFilter" o = DeviceMonitorAddFilterMethodInfo
    ResolveDeviceMonitorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDeviceMonitorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDeviceMonitorMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
    ResolveDeviceMonitorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDeviceMonitorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDeviceMonitorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDeviceMonitorMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
    ResolveDeviceMonitorMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
    ResolveDeviceMonitorMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
    ResolveDeviceMonitorMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
    ResolveDeviceMonitorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDeviceMonitorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDeviceMonitorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDeviceMonitorMethod "ref" o = Gst.Object.ObjectRefMethodInfo
    ResolveDeviceMonitorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDeviceMonitorMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
    ResolveDeviceMonitorMethod "removeFilter" o = DeviceMonitorRemoveFilterMethodInfo
    ResolveDeviceMonitorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDeviceMonitorMethod "start" o = DeviceMonitorStartMethodInfo
    ResolveDeviceMonitorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDeviceMonitorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDeviceMonitorMethod "stop" o = DeviceMonitorStopMethodInfo
    ResolveDeviceMonitorMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
    ResolveDeviceMonitorMethod "syncValues" o = Gst.Object.ObjectSyncValuesMethodInfo
    ResolveDeviceMonitorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDeviceMonitorMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
    ResolveDeviceMonitorMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
    ResolveDeviceMonitorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDeviceMonitorMethod "getBus" o = DeviceMonitorGetBusMethodInfo
    ResolveDeviceMonitorMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
    ResolveDeviceMonitorMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
    ResolveDeviceMonitorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDeviceMonitorMethod "getDevices" o = DeviceMonitorGetDevicesMethodInfo
    ResolveDeviceMonitorMethod "getGValueArray" o = Gst.Object.ObjectGetGValueArrayMethodInfo
    ResolveDeviceMonitorMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
    ResolveDeviceMonitorMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
    ResolveDeviceMonitorMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
    ResolveDeviceMonitorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDeviceMonitorMethod "getProviders" o = DeviceMonitorGetProvidersMethodInfo
    ResolveDeviceMonitorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDeviceMonitorMethod "getShowAllDevices" o = DeviceMonitorGetShowAllDevicesMethodInfo
    ResolveDeviceMonitorMethod "getValue" o = Gst.Object.ObjectGetValueMethodInfo
    ResolveDeviceMonitorMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
    ResolveDeviceMonitorMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
    ResolveDeviceMonitorMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
    ResolveDeviceMonitorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDeviceMonitorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDeviceMonitorMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
    ResolveDeviceMonitorMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
    ResolveDeviceMonitorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDeviceMonitorMethod "setShowAllDevices" o = DeviceMonitorSetShowAllDevicesMethodInfo
    ResolveDeviceMonitorMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "show-all"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@show-all@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' deviceMonitor [ #showAll 'Data.GI.Base.Attributes.:=' value ]
-- @
setDeviceMonitorShowAll :: (MonadIO m, IsDeviceMonitor o) => o -> Bool -> m ()
setDeviceMonitorShowAll :: o -> Bool -> m ()
setDeviceMonitorShowAll obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "show-all" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorShowAllPropertyInfo
instance AttrInfo DeviceMonitorShowAllPropertyInfo where
    type AttrAllowedOps DeviceMonitorShowAllPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceMonitorShowAllPropertyInfo = IsDeviceMonitor
    type AttrSetTypeConstraint DeviceMonitorShowAllPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint DeviceMonitorShowAllPropertyInfo = (~) Bool
    type AttrTransferType DeviceMonitorShowAllPropertyInfo = Bool
    type AttrGetType DeviceMonitorShowAllPropertyInfo = Bool
    type AttrLabel DeviceMonitorShowAllPropertyInfo = "show-all"
    type AttrOrigin DeviceMonitorShowAllPropertyInfo = DeviceMonitor
    attrGet = getDeviceMonitorShowAll
    attrSet = setDeviceMonitorShowAll
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceMonitorShowAll
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DeviceMonitor
type instance O.AttributeList DeviceMonitor = DeviceMonitorAttributeList
type DeviceMonitorAttributeList = ('[ '("name", Gst.Object.ObjectNamePropertyInfo), '("parent", Gst.Object.ObjectParentPropertyInfo), '("showAll", DeviceMonitorShowAllPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
deviceMonitorShowAll :: AttrLabelProxy "showAll"
deviceMonitorShowAll = AttrLabelProxy

#endif

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

#endif

-- method DeviceMonitor::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gst" , name = "DeviceMonitor" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_monitor_new" gst_device_monitor_new :: 
    IO (Ptr DeviceMonitor)

-- | Create a new t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor'
-- 
-- /Since: 1.4/
deviceMonitorNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m DeviceMonitor
    -- ^ __Returns:__ a new device monitor.
deviceMonitorNew :: m DeviceMonitor
deviceMonitorNew  = IO DeviceMonitor -> m DeviceMonitor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceMonitor -> m DeviceMonitor)
-> IO DeviceMonitor -> m DeviceMonitor
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceMonitor
result <- IO (Ptr DeviceMonitor)
gst_device_monitor_new
    Text -> Ptr DeviceMonitor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "deviceMonitorNew" Ptr DeviceMonitor
result
    DeviceMonitor
result' <- ((ManagedPtr DeviceMonitor -> DeviceMonitor)
-> Ptr DeviceMonitor -> IO DeviceMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DeviceMonitor -> DeviceMonitor
DeviceMonitor) Ptr DeviceMonitor
result
    DeviceMonitor -> IO DeviceMonitor
forall (m :: * -> *) a. Monad m => a -> m a
return DeviceMonitor
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method DeviceMonitor::add_filter
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "monitor"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "DeviceMonitor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a device monitor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "classes"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "device classes to use as filter or %NULL for any class"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "caps"
--           , argType = TInterface Name { namespace = "Gst" , name = "Caps" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstCaps to filter or %NULL for ANY"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_monitor_add_filter" gst_device_monitor_add_filter :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    CString ->                              -- classes : TBasicType TUTF8
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO Word32

-- | Adds a filter for which t'GI.Gst.Objects.Device.Device' will be monitored, any device that matches
-- all these classes and the t'GI.Gst.Structs.Caps.Caps' will be returned.
-- 
-- If this function is called multiple times to add more filters, each will be
-- matched independently. That is, adding more filters will not further restrict
-- what devices are matched.
-- 
-- The t'GI.Gst.Structs.Caps.Caps' supported by the device as returned by 'GI.Gst.Objects.Device.deviceGetCaps' are
-- not intersected with caps filters added using this function.
-- 
-- Filters must be added before the t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor' is started.
-- 
-- /Since: 1.4/
deviceMonitorAddFilter ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: a device monitor
    -> Maybe (T.Text)
    -- ^ /@classes@/: device classes to use as filter or 'P.Nothing' for any class
    -> Maybe (Gst.Caps.Caps)
    -- ^ /@caps@/: the t'GI.Gst.Structs.Caps.Caps' to filter or 'P.Nothing' for ANY
    -> m Word32
    -- ^ __Returns:__ The id of the new filter or 0 if no provider matched the filter\'s
    --  classes.
deviceMonitorAddFilter :: a -> Maybe Text -> Maybe Caps -> m Word32
deviceMonitorAddFilter monitor :: a
monitor classes :: Maybe Text
classes caps :: Maybe Caps
caps = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    Ptr CChar
maybeClasses <- case Maybe Text
classes of
        Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just jClasses :: Text
jClasses -> do
            Ptr CChar
jClasses' <- Text -> IO (Ptr CChar)
textToCString Text
jClasses
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jClasses'
    Ptr Caps
maybeCaps <- case Maybe Caps
caps of
        Nothing -> Ptr Caps -> IO (Ptr Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
forall a. Ptr a
nullPtr
        Just jCaps :: Caps
jCaps -> do
            Ptr Caps
jCaps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
jCaps
            Ptr Caps -> IO (Ptr Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
jCaps'
    Word32
result <- Ptr DeviceMonitor -> Ptr CChar -> Ptr Caps -> IO Word32
gst_device_monitor_add_filter Ptr DeviceMonitor
monitor' Ptr CChar
maybeClasses Ptr Caps
maybeCaps
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
    Maybe Caps -> (Caps -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Caps
caps Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeClasses
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorAddFilterMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (Gst.Caps.Caps) -> m Word32), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorAddFilterMethodInfo a signature where
    overloadedMethod = deviceMonitorAddFilter

#endif

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

foreign import ccall "gst_device_monitor_get_bus" gst_device_monitor_get_bus :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    IO (Ptr Gst.Bus.Bus)

-- | Gets the t'GI.Gst.Objects.Bus.Bus' of this t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor'
-- 
-- /Since: 1.4/
deviceMonitorGetBus ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: a t'GI.Gst.Objects.DeviceProvider.DeviceProvider'
    -> m Gst.Bus.Bus
    -- ^ __Returns:__ a t'GI.Gst.Objects.Bus.Bus'
deviceMonitorGetBus :: a -> m Bus
deviceMonitorGetBus monitor :: a
monitor = IO Bus -> m Bus
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bus -> m Bus) -> IO Bus -> m Bus
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    Ptr Bus
result <- Ptr DeviceMonitor -> IO (Ptr Bus)
gst_device_monitor_get_bus Ptr DeviceMonitor
monitor'
    Text -> Ptr Bus -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "deviceMonitorGetBus" Ptr Bus
result
    Bus
result' <- ((ManagedPtr Bus -> Bus) -> Ptr Bus -> IO Bus
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Bus -> Bus
Gst.Bus.Bus) Ptr Bus
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
    Bus -> IO Bus
forall (m :: * -> *) a. Monad m => a -> m a
return Bus
result'

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorGetBusMethodInfo
instance (signature ~ (m Gst.Bus.Bus), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorGetBusMethodInfo a signature where
    overloadedMethod = deviceMonitorGetBus

#endif

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

foreign import ccall "gst_device_monitor_get_devices" gst_device_monitor_get_devices :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    IO (Ptr (GList (Ptr Gst.Device.Device)))

-- | Gets a list of devices from all of the relevant monitors. This may actually
-- probe the hardware if the monitor is not currently started.
-- 
-- /Since: 1.4/
deviceMonitorGetDevices ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: A t'GI.Gst.Objects.DeviceProvider.DeviceProvider'
    -> m [Gst.Device.Device]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of
    --   t'GI.Gst.Objects.Device.Device'
deviceMonitorGetDevices :: a -> m [Device]
deviceMonitorGetDevices monitor :: a
monitor = IO [Device] -> m [Device]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Device] -> m [Device]) -> IO [Device] -> m [Device]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    Ptr (GList (Ptr Device))
result <- Ptr DeviceMonitor -> IO (Ptr (GList (Ptr Device)))
gst_device_monitor_get_devices Ptr DeviceMonitor
monitor'
    [Ptr Device]
result' <- Ptr (GList (Ptr Device)) -> IO [Ptr Device]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Device))
result
    [Device]
result'' <- (Ptr Device -> IO Device) -> [Ptr Device] -> IO [Device]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Device -> Device
Gst.Device.Device) [Ptr Device]
result'
    Ptr (GList (Ptr Device)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Device))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
    [Device] -> IO [Device]
forall (m :: * -> *) a. Monad m => a -> m a
return [Device]
result''

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorGetDevicesMethodInfo
instance (signature ~ (m [Gst.Device.Device]), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorGetDevicesMethodInfo a signature where
    overloadedMethod = deviceMonitorGetDevices

#endif

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

foreign import ccall "gst_device_monitor_get_providers" gst_device_monitor_get_providers :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    IO (Ptr CString)

-- | Get a list of the currently selected device provider factories.
-- 
-- This
-- 
-- /Since: 1.6/
deviceMonitorGetProviders ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: a t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor'
    -> m [T.Text]
    -- ^ __Returns:__ 
    --     A list of device provider factory names that are currently being
    --     monitored by /@monitor@/ or 'P.Nothing' when nothing is being monitored.
deviceMonitorGetProviders :: a -> m [Text]
deviceMonitorGetProviders monitor :: a
monitor = 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 DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    Ptr (Ptr CChar)
result <- Ptr DeviceMonitor -> IO (Ptr (Ptr CChar))
gst_device_monitor_get_providers Ptr DeviceMonitor
monitor'
    Text -> Ptr (Ptr CChar) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "deviceMonitorGetProviders" Ptr (Ptr CChar)
result
    [Text]
result' <- HasCallStack => Ptr (Ptr CChar) -> IO [Text]
Ptr (Ptr CChar) -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr (Ptr CChar)
result
    (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)
result
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorGetProvidersMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorGetProvidersMethodInfo a signature where
    overloadedMethod = deviceMonitorGetProviders

#endif

-- method DeviceMonitor::get_show_all_devices
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "monitor"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "DeviceMonitor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstDeviceMonitor"
--                 , 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_monitor_get_show_all_devices" gst_device_monitor_get_show_all_devices :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    IO CInt

-- | Get if /@monitor@/ is curretly showing all devices, even those from hidden
-- providers.
-- 
-- /Since: 1.6/
deviceMonitorGetShowAllDevices ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: a t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor'
    -> m Bool
    -- ^ __Returns:__ 'P.True' when all devices will be shown.
deviceMonitorGetShowAllDevices :: a -> m Bool
deviceMonitorGetShowAllDevices monitor :: a
monitor = 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 DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    CInt
result <- Ptr DeviceMonitor -> IO CInt
gst_device_monitor_get_show_all_devices Ptr DeviceMonitor
monitor'
    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
monitor
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorGetShowAllDevicesMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorGetShowAllDevicesMethodInfo a signature where
    overloadedMethod = deviceMonitorGetShowAllDevices

#endif

-- method DeviceMonitor::remove_filter
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "monitor"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "DeviceMonitor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a device monitor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filter_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the id of the filter"
--                 , 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_monitor_remove_filter" gst_device_monitor_remove_filter :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    Word32 ->                               -- filter_id : TBasicType TUInt
    IO CInt

-- | Removes a filter from the t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor' using the id that was returned
-- by 'GI.Gst.Objects.DeviceMonitor.deviceMonitorAddFilter'.
-- 
-- /Since: 1.4/
deviceMonitorRemoveFilter ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: a device monitor
    -> Word32
    -- ^ /@filterId@/: the id of the filter
    -> m Bool
    -- ^ __Returns:__ 'P.True' of the filter id was valid, 'P.False' otherwise
deviceMonitorRemoveFilter :: a -> Word32 -> m Bool
deviceMonitorRemoveFilter monitor :: a
monitor filterId :: Word32
filterId = 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 DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    CInt
result <- Ptr DeviceMonitor -> Word32 -> IO CInt
gst_device_monitor_remove_filter Ptr DeviceMonitor
monitor' Word32
filterId
    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
monitor
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorRemoveFilterMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorRemoveFilterMethodInfo a signature where
    overloadedMethod = deviceMonitorRemoveFilter

#endif

-- method DeviceMonitor::set_show_all_devices
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "monitor"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "DeviceMonitor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstDeviceMonitor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "show_all"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "show all devices" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_monitor_set_show_all_devices" gst_device_monitor_set_show_all_devices :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    CInt ->                                 -- show_all : TBasicType TBoolean
    IO ()

-- | Set if all devices should be visible, even those devices from hidden
-- providers. Setting /@showAll@/ to true might show some devices multiple times.
-- 
-- /Since: 1.6/
deviceMonitorSetShowAllDevices ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: a t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor'
    -> Bool
    -- ^ /@showAll@/: show all devices
    -> m ()
deviceMonitorSetShowAllDevices :: a -> Bool -> m ()
deviceMonitorSetShowAllDevices monitor :: a
monitor showAll :: Bool
showAll = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    let showAll' :: CInt
showAll' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
showAll
    Ptr DeviceMonitor -> CInt -> IO ()
gst_device_monitor_set_show_all_devices Ptr DeviceMonitor
monitor' CInt
showAll'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorSetShowAllDevicesMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorSetShowAllDevicesMethodInfo a signature where
    overloadedMethod = deviceMonitorSetShowAllDevices

#endif

-- method DeviceMonitor::start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "monitor"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "DeviceMonitor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GstDeviceMonitor"
--                 , 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_monitor_start" gst_device_monitor_start :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    IO CInt

-- | Starts monitoring the devices, one this has succeeded, the
-- 'GI.Gst.Flags.MessageTypeDeviceAdded' and 'GI.Gst.Flags.MessageTypeDeviceRemoved' messages
-- will be emitted on the bus when the list of devices changes.
-- 
-- /Since: 1.4/
deviceMonitorStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: A t'GI.Gst.Objects.DeviceMonitor.DeviceMonitor'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the device monitoring could be started
deviceMonitorStart :: a -> m Bool
deviceMonitorStart monitor :: a
monitor = 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 DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    CInt
result <- Ptr DeviceMonitor -> IO CInt
gst_device_monitor_start Ptr DeviceMonitor
monitor'
    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
monitor
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorStartMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorStartMethodInfo a signature where
    overloadedMethod = deviceMonitorStart

#endif

-- method DeviceMonitor::stop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "monitor"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "DeviceMonitor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GstDeviceProvider"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_device_monitor_stop" gst_device_monitor_stop :: 
    Ptr DeviceMonitor ->                    -- monitor : TInterface (Name {namespace = "Gst", name = "DeviceMonitor"})
    IO ()

-- | Stops monitoring the devices.
-- 
-- /Since: 1.4/
deviceMonitorStop ::
    (B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
    a
    -- ^ /@monitor@/: A t'GI.Gst.Objects.DeviceProvider.DeviceProvider'
    -> m ()
deviceMonitorStop :: a -> m ()
deviceMonitorStop monitor :: a
monitor = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DeviceMonitor
monitor' <- a -> IO (Ptr DeviceMonitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
    Ptr DeviceMonitor -> IO ()
gst_device_monitor_stop Ptr DeviceMonitor
monitor'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DeviceMonitorStopMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDeviceMonitor a) => O.MethodInfo DeviceMonitorStopMethodInfo a signature where
    overloadedMethod = deviceMonitorStop

#endif