{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Objects.DeviceMonitor
(
DeviceMonitor(..) ,
IsDeviceMonitor ,
toDeviceMonitor ,
#if defined(ENABLE_OVERLOADING)
ResolveDeviceMonitorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceMonitorAddFilterMethodInfo ,
#endif
deviceMonitorAddFilter ,
#if defined(ENABLE_OVERLOADING)
DeviceMonitorGetBusMethodInfo ,
#endif
deviceMonitorGetBus ,
#if defined(ENABLE_OVERLOADING)
DeviceMonitorGetDevicesMethodInfo ,
#endif
deviceMonitorGetDevices ,
#if defined(ENABLE_OVERLOADING)
DeviceMonitorGetProvidersMethodInfo ,
#endif
deviceMonitorGetProviders ,
#if defined(ENABLE_OVERLOADING)
DeviceMonitorGetShowAllDevicesMethodInfo,
#endif
deviceMonitorGetShowAllDevices ,
deviceMonitorNew ,
#if defined(ENABLE_OVERLOADING)
DeviceMonitorRemoveFilterMethodInfo ,
#endif
deviceMonitorRemoveFilter ,
#if defined(ENABLE_OVERLOADING)
DeviceMonitorSetShowAllDevicesMethodInfo,
#endif
deviceMonitorSetShowAllDevices ,
#if defined(ENABLE_OVERLOADING)
DeviceMonitorStartMethodInfo ,
#endif
deviceMonitorStart ,
#if defined(ENABLE_OVERLOADING)
DeviceMonitorStopMethodInfo ,
#endif
deviceMonitorStop ,
#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.Date as GLib.Date
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GLib.Unions.Mutex as GLib.Mutex
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.ValueArray as GObject.ValueArray
import qualified GI.Gst.Callbacks as Gst.Callbacks
import {-# SOURCE #-} qualified GI.Gst.Enums as Gst.Enums
import {-# SOURCE #-} qualified GI.Gst.Flags as Gst.Flags
import {-# SOURCE #-} qualified GI.Gst.Objects.Allocator as Gst.Allocator
import {-# SOURCE #-} qualified GI.Gst.Objects.BufferPool as Gst.BufferPool
import {-# SOURCE #-} qualified GI.Gst.Objects.Bus as Gst.Bus
import {-# SOURCE #-} qualified GI.Gst.Objects.Clock as Gst.Clock
import {-# SOURCE #-} qualified GI.Gst.Objects.ControlBinding as Gst.ControlBinding
import {-# SOURCE #-} qualified GI.Gst.Objects.Device as Gst.Device
import {-# SOURCE #-} qualified GI.Gst.Objects.Element as Gst.Element
import {-# SOURCE #-} qualified GI.Gst.Objects.ElementFactory as Gst.ElementFactory
import {-# SOURCE #-} qualified GI.Gst.Objects.Object as Gst.Object
import {-# SOURCE #-} qualified GI.Gst.Objects.Pad as Gst.Pad
import {-# SOURCE #-} qualified GI.Gst.Objects.PadTemplate as Gst.PadTemplate
import {-# SOURCE #-} qualified GI.Gst.Objects.Plugin as Gst.Plugin
import {-# SOURCE #-} qualified GI.Gst.Objects.PluginFeature as Gst.PluginFeature
import {-# SOURCE #-} qualified GI.Gst.Objects.Stream as Gst.Stream
import {-# SOURCE #-} qualified GI.Gst.Objects.StreamCollection as Gst.StreamCollection
import {-# SOURCE #-} qualified GI.Gst.Structs.AllocationParams as Gst.AllocationParams
import {-# SOURCE #-} qualified GI.Gst.Structs.Buffer as Gst.Buffer
import {-# SOURCE #-} qualified GI.Gst.Structs.BufferList as Gst.BufferList
import {-# SOURCE #-} qualified GI.Gst.Structs.BufferPoolAcquireParams as Gst.BufferPoolAcquireParams
import {-# SOURCE #-} qualified GI.Gst.Structs.ByteArrayInterface as Gst.ByteArrayInterface
import {-# SOURCE #-} qualified GI.Gst.Structs.Caps as Gst.Caps
import {-# SOURCE #-} qualified GI.Gst.Structs.CapsFeatures as Gst.CapsFeatures
import {-# SOURCE #-} qualified GI.Gst.Structs.Context as Gst.Context
import {-# SOURCE #-} qualified GI.Gst.Structs.CustomMeta as Gst.CustomMeta
import {-# SOURCE #-} qualified GI.Gst.Structs.DateTime as Gst.DateTime
import {-# SOURCE #-} qualified GI.Gst.Structs.Event as Gst.Event
import {-# SOURCE #-} qualified GI.Gst.Structs.Iterator as Gst.Iterator
import {-# SOURCE #-} qualified GI.Gst.Structs.MapInfo as Gst.MapInfo
import {-# SOURCE #-} qualified GI.Gst.Structs.Memory as Gst.Memory
import {-# SOURCE #-} qualified GI.Gst.Structs.Message as Gst.Message
import {-# SOURCE #-} qualified GI.Gst.Structs.Meta as Gst.Meta
import {-# SOURCE #-} qualified GI.Gst.Structs.MetaInfo as Gst.MetaInfo
import {-# SOURCE #-} qualified GI.Gst.Structs.MiniObject as Gst.MiniObject
import {-# SOURCE #-} qualified GI.Gst.Structs.ParentBufferMeta as Gst.ParentBufferMeta
import {-# SOURCE #-} qualified GI.Gst.Structs.ProtectionMeta as Gst.ProtectionMeta
import {-# SOURCE #-} qualified GI.Gst.Structs.Query as Gst.Query
import {-# SOURCE #-} qualified GI.Gst.Structs.ReferenceTimestampMeta as Gst.ReferenceTimestampMeta
import {-# SOURCE #-} qualified GI.Gst.Structs.Sample as Gst.Sample
import {-# SOURCE #-} qualified GI.Gst.Structs.Segment as Gst.Segment
import {-# SOURCE #-} qualified GI.Gst.Structs.StaticCaps as Gst.StaticCaps
import {-# SOURCE #-} qualified GI.Gst.Structs.StaticPadTemplate as Gst.StaticPadTemplate
import {-# SOURCE #-} qualified GI.Gst.Structs.Structure as Gst.Structure
import {-# SOURCE #-} qualified GI.Gst.Structs.TagList as Gst.TagList
import {-# SOURCE #-} qualified GI.Gst.Structs.Toc as Gst.Toc
import {-# SOURCE #-} qualified GI.Gst.Structs.TocEntry as Gst.TocEntry
#else
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
#endif
newtype DeviceMonitor = DeviceMonitor (SP.ManagedPtr DeviceMonitor)
deriving (DeviceMonitor -> DeviceMonitor -> Bool
(DeviceMonitor -> DeviceMonitor -> Bool)
-> (DeviceMonitor -> DeviceMonitor -> Bool) -> Eq DeviceMonitor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeviceMonitor -> DeviceMonitor -> Bool
== :: DeviceMonitor -> DeviceMonitor -> Bool
$c/= :: DeviceMonitor -> DeviceMonitor -> Bool
/= :: DeviceMonitor -> DeviceMonitor -> Bool
Eq)
instance SP.ManagedPtrNewtype DeviceMonitor where
toManagedPtr :: DeviceMonitor -> ManagedPtr DeviceMonitor
toManagedPtr (DeviceMonitor ManagedPtr DeviceMonitor
p) = ManagedPtr DeviceMonitor
p
foreign import ccall "gst_device_monitor_get_type"
c_gst_device_monitor_get_type :: IO B.Types.GType
instance B.Types.TypedObject DeviceMonitor where
glibType :: IO GType
glibType = IO GType
c_gst_device_monitor_get_type
instance B.Types.GObject DeviceMonitor
class (SP.GObject o, O.IsDescendantOf DeviceMonitor o) => IsDeviceMonitor o
instance (SP.GObject o, O.IsDescendantOf DeviceMonitor o) => IsDeviceMonitor o
instance O.HasParentTypes DeviceMonitor
type instance O.ParentTypes DeviceMonitor = '[Gst.Object.Object, GObject.Object.Object]
toDeviceMonitor :: (MIO.MonadIO m, IsDeviceMonitor o) => o -> m DeviceMonitor
toDeviceMonitor :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceMonitor o) =>
o -> m DeviceMonitor
toDeviceMonitor = IO DeviceMonitor -> m DeviceMonitor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DeviceMonitor -> DeviceMonitor
DeviceMonitor
instance B.GValue.IsGValue (Maybe DeviceMonitor) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gst_device_monitor_get_type
gvalueSet_ :: Ptr GValue -> Maybe DeviceMonitor -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DeviceMonitor
P.Nothing = Ptr GValue -> Ptr DeviceMonitor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DeviceMonitor
forall a. Ptr a
FP.nullPtr :: FP.Ptr DeviceMonitor)
gvalueSet_ Ptr GValue
gv (P.Just DeviceMonitor
obj) = DeviceMonitor -> (Ptr DeviceMonitor -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DeviceMonitor
obj (Ptr GValue -> Ptr DeviceMonitor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DeviceMonitor)
gvalueGet_ Ptr GValue
gv = do
Ptr DeviceMonitor
ptr <- Ptr GValue -> IO (Ptr DeviceMonitor)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DeviceMonitor)
if Ptr DeviceMonitor
ptr Ptr DeviceMonitor -> Ptr DeviceMonitor -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DeviceMonitor
forall a. Ptr a
FP.nullPtr
then DeviceMonitor -> Maybe DeviceMonitor
forall a. a -> Maybe a
P.Just (DeviceMonitor -> Maybe DeviceMonitor)
-> IO DeviceMonitor -> IO (Maybe DeviceMonitor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
else Maybe DeviceMonitor -> IO (Maybe DeviceMonitor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeviceMonitor
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceMonitorMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDeviceMonitorMethod t DeviceMonitor, O.OverloadedMethod info DeviceMonitor p, R.HasField t DeviceMonitor p) => R.HasField t DeviceMonitor p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDeviceMonitorMethod t DeviceMonitor, O.OverloadedMethodInfo info DeviceMonitor) => OL.IsLabel t (O.MethodProxy info DeviceMonitor) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getDeviceMonitorShowAll :: (MonadIO m, IsDeviceMonitor o) => o -> m Bool
getDeviceMonitorShowAll :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceMonitor o) =>
o -> m Bool
getDeviceMonitorShowAll o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"show-all"
setDeviceMonitorShowAll :: (MonadIO m, IsDeviceMonitor o) => o -> Bool -> m ()
setDeviceMonitorShowAll :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceMonitor o) =>
o -> Bool -> m ()
setDeviceMonitorShowAll o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"show-all" Bool
val
constructDeviceMonitorShowAll :: (IsDeviceMonitor o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDeviceMonitorShowAll :: forall o (m :: * -> *).
(IsDeviceMonitor o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDeviceMonitorShowAll Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.showAll"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#g:attr:showAll"
})
#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, DK.Type)])
#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, DK.Type)])
#endif
foreign import ccall "gst_device_monitor_new" gst_device_monitor_new ::
IO (Ptr DeviceMonitor)
deviceMonitorNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m DeviceMonitor
deviceMonitorNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m DeviceMonitor
deviceMonitorNew = IO DeviceMonitor -> m DeviceMonitor
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DeviceMonitor
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gst_device_monitor_add_filter" gst_device_monitor_add_filter ::
Ptr DeviceMonitor ->
CString ->
Ptr Gst.Caps.Caps ->
IO Word32
deviceMonitorAddFilter ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> Maybe (T.Text)
-> Maybe (Gst.Caps.Caps)
-> m Word32
deviceMonitorAddFilter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> Maybe Text -> Maybe Caps -> m Word32
deviceMonitorAddFilter a
monitor Maybe Text
classes Maybe Caps
caps = IO Word32 -> m Word32
forall a. IO a -> m a
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
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jClasses -> do
Ptr CChar
jClasses' <- Text -> IO (Ptr CChar)
textToCString Text
jClasses
Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jClasses'
Ptr Caps
maybeCaps <- case Maybe Caps
caps of
Maybe Caps
Nothing -> Ptr Caps -> IO (Ptr Caps)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
forall a. Ptr a
nullPtr
Just 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 a. a -> IO a
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 a. a -> IO a
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.OverloadedMethod DeviceMonitorAddFilterMethodInfo a signature where
overloadedMethod = deviceMonitorAddFilter
instance O.OverloadedMethodInfo DeviceMonitorAddFilterMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorAddFilter",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorAddFilter"
})
#endif
foreign import ccall "gst_device_monitor_get_bus" gst_device_monitor_get_bus ::
Ptr DeviceMonitor ->
IO (Ptr Gst.Bus.Bus)
deviceMonitorGetBus ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> m Gst.Bus.Bus
deviceMonitorGetBus :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> m Bus
deviceMonitorGetBus a
monitor = IO Bus -> m Bus
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DeviceMonitorGetBusMethodInfo a signature where
overloadedMethod = deviceMonitorGetBus
instance O.OverloadedMethodInfo DeviceMonitorGetBusMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorGetBus",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorGetBus"
})
#endif
foreign import ccall "gst_device_monitor_get_devices" gst_device_monitor_get_devices ::
Ptr DeviceMonitor ->
IO (Ptr (GList (Ptr Gst.Device.Device)))
deviceMonitorGetDevices ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> m [Gst.Device.Device]
deviceMonitorGetDevices :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> m [Device]
deviceMonitorGetDevices a
monitor = IO [Device] -> m [Device]
forall a. IO a -> m a
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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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 a. a -> IO a
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.OverloadedMethod DeviceMonitorGetDevicesMethodInfo a signature where
overloadedMethod = deviceMonitorGetDevices
instance O.OverloadedMethodInfo DeviceMonitorGetDevicesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorGetDevices",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorGetDevices"
})
#endif
foreign import ccall "gst_device_monitor_get_providers" gst_device_monitor_get_providers ::
Ptr DeviceMonitor ->
IO (Ptr CString)
deviceMonitorGetProviders ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> m [T.Text]
deviceMonitorGetProviders :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> m [Text]
deviceMonitorGetProviders a
monitor = IO [Text] -> m [Text]
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod DeviceMonitorGetProvidersMethodInfo a signature where
overloadedMethod = deviceMonitorGetProviders
instance O.OverloadedMethodInfo DeviceMonitorGetProvidersMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorGetProviders",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorGetProviders"
})
#endif
foreign import ccall "gst_device_monitor_get_show_all_devices" gst_device_monitor_get_show_all_devices ::
Ptr DeviceMonitor ->
IO CInt
deviceMonitorGetShowAllDevices ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> m Bool
deviceMonitorGetShowAllDevices :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> m Bool
deviceMonitorGetShowAllDevices a
monitor = IO Bool -> m Bool
forall a. IO a -> m a
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
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
Bool -> IO Bool
forall a. a -> IO a
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.OverloadedMethod DeviceMonitorGetShowAllDevicesMethodInfo a signature where
overloadedMethod = deviceMonitorGetShowAllDevices
instance O.OverloadedMethodInfo DeviceMonitorGetShowAllDevicesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorGetShowAllDevices",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorGetShowAllDevices"
})
#endif
foreign import ccall "gst_device_monitor_remove_filter" gst_device_monitor_remove_filter ::
Ptr DeviceMonitor ->
Word32 ->
IO CInt
deviceMonitorRemoveFilter ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> Word32
-> m Bool
deviceMonitorRemoveFilter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> Word32 -> m Bool
deviceMonitorRemoveFilter a
monitor Word32
filterId = IO Bool -> m Bool
forall a. IO a -> m a
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
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
Bool -> IO Bool
forall a. a -> IO a
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.OverloadedMethod DeviceMonitorRemoveFilterMethodInfo a signature where
overloadedMethod = deviceMonitorRemoveFilter
instance O.OverloadedMethodInfo DeviceMonitorRemoveFilterMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorRemoveFilter",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorRemoveFilter"
})
#endif
foreign import ccall "gst_device_monitor_set_show_all_devices" gst_device_monitor_set_show_all_devices ::
Ptr DeviceMonitor ->
CInt ->
IO ()
deviceMonitorSetShowAllDevices ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> Bool
-> m ()
deviceMonitorSetShowAllDevices :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> Bool -> m ()
deviceMonitorSetShowAllDevices a
monitor Bool
showAll = IO () -> m ()
forall a. IO a -> m a
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
P.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
P.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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DeviceMonitorSetShowAllDevicesMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDeviceMonitor a) => O.OverloadedMethod DeviceMonitorSetShowAllDevicesMethodInfo a signature where
overloadedMethod = deviceMonitorSetShowAllDevices
instance O.OverloadedMethodInfo DeviceMonitorSetShowAllDevicesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorSetShowAllDevices",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorSetShowAllDevices"
})
#endif
foreign import ccall "gst_device_monitor_start" gst_device_monitor_start ::
Ptr DeviceMonitor ->
IO CInt
deviceMonitorStart ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> m Bool
deviceMonitorStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> m Bool
deviceMonitorStart a
monitor = IO Bool -> m Bool
forall a. IO a -> m a
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
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
Bool -> IO Bool
forall a. a -> IO a
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.OverloadedMethod DeviceMonitorStartMethodInfo a signature where
overloadedMethod = deviceMonitorStart
instance O.OverloadedMethodInfo DeviceMonitorStartMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorStart",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorStart"
})
#endif
foreign import ccall "gst_device_monitor_stop" gst_device_monitor_stop ::
Ptr DeviceMonitor ->
IO ()
deviceMonitorStop ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a
-> m ()
deviceMonitorStop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceMonitor a) =>
a -> m ()
deviceMonitorStop a
monitor = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DeviceMonitorStopMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDeviceMonitor a) => O.OverloadedMethod DeviceMonitorStopMethodInfo a signature where
overloadedMethod = deviceMonitorStop
instance O.OverloadedMethodInfo DeviceMonitorStopMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.DeviceMonitor.deviceMonitorStop",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-DeviceMonitor.html#v:deviceMonitorStop"
})
#endif