{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Objects.Device
(
Device(..) ,
IsDevice ,
toDevice ,
#if defined(ENABLE_OVERLOADING)
ResolveDeviceMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceCreateElementMethodInfo ,
#endif
deviceCreateElement ,
#if defined(ENABLE_OVERLOADING)
DeviceGetCapsMethodInfo ,
#endif
deviceGetCaps ,
#if defined(ENABLE_OVERLOADING)
DeviceGetDeviceClassMethodInfo ,
#endif
deviceGetDeviceClass ,
#if defined(ENABLE_OVERLOADING)
DeviceGetDisplayNameMethodInfo ,
#endif
deviceGetDisplayName ,
#if defined(ENABLE_OVERLOADING)
DeviceGetPropertiesMethodInfo ,
#endif
deviceGetProperties ,
#if defined(ENABLE_OVERLOADING)
DeviceHasClassesMethodInfo ,
#endif
deviceHasClasses ,
#if defined(ENABLE_OVERLOADING)
DeviceHasClassesvMethodInfo ,
#endif
deviceHasClassesv ,
#if defined(ENABLE_OVERLOADING)
DeviceReconfigureElementMethodInfo ,
#endif
deviceReconfigureElement ,
#if defined(ENABLE_OVERLOADING)
DeviceCapsPropertyInfo ,
#endif
constructDeviceCaps ,
#if defined(ENABLE_OVERLOADING)
deviceCaps ,
#endif
getDeviceCaps ,
#if defined(ENABLE_OVERLOADING)
DeviceDeviceClassPropertyInfo ,
#endif
constructDeviceDeviceClass ,
#if defined(ENABLE_OVERLOADING)
deviceDeviceClass ,
#endif
getDeviceDeviceClass ,
#if defined(ENABLE_OVERLOADING)
DeviceDisplayNamePropertyInfo ,
#endif
constructDeviceDisplayName ,
#if defined(ENABLE_OVERLOADING)
deviceDisplayName ,
#endif
getDeviceDisplayName ,
#if defined(ENABLE_OVERLOADING)
DevicePropertiesPropertyInfo ,
#endif
constructDeviceProperties ,
#if defined(ENABLE_OVERLOADING)
deviceProperties ,
#endif
getDeviceProperties ,
DeviceRemovedCallback ,
#if defined(ENABLE_OVERLOADING)
DeviceRemovedSignalInfo ,
#endif
afterDeviceRemoved ,
onDeviceRemoved ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gst.Objects.Element as Gst.Element
import {-# SOURCE #-} qualified GI.Gst.Objects.Object as Gst.Object
import {-# SOURCE #-} qualified GI.Gst.Structs.Caps as Gst.Caps
import {-# SOURCE #-} qualified GI.Gst.Structs.Structure as Gst.Structure
newtype Device = Device (SP.ManagedPtr Device)
deriving (Device -> Device -> Bool
(Device -> Device -> Bool)
-> (Device -> Device -> Bool) -> Eq Device
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Device -> Device -> Bool
$c/= :: Device -> Device -> Bool
== :: Device -> Device -> Bool
$c== :: Device -> Device -> Bool
Eq)
instance SP.ManagedPtrNewtype Device where
toManagedPtr :: Device -> ManagedPtr Device
toManagedPtr (Device ManagedPtr Device
p) = ManagedPtr Device
p
foreign import ccall "gst_device_get_type"
c_gst_device_get_type :: IO B.Types.GType
instance B.Types.TypedObject Device where
glibType :: IO GType
glibType = IO GType
c_gst_device_get_type
instance B.Types.GObject Device
class (SP.GObject o, O.IsDescendantOf Device o) => IsDevice o
instance (SP.GObject o, O.IsDescendantOf Device o) => IsDevice o
instance O.HasParentTypes Device
type instance O.ParentTypes Device = '[Gst.Object.Object, GObject.Object.Object]
toDevice :: (MIO.MonadIO m, IsDevice o) => o -> m Device
toDevice :: forall (m :: * -> *) o. (MonadIO m, IsDevice o) => o -> m Device
toDevice = IO Device -> m Device
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Device -> m Device) -> (o -> IO Device) -> o -> m Device
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Device -> Device) -> o -> IO Device
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Device -> Device
Device
instance B.GValue.IsGValue (Maybe Device) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gst_device_get_type
gvalueSet_ :: Ptr GValue -> Maybe Device -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Device
P.Nothing = Ptr GValue -> Ptr Device -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Device
forall a. Ptr a
FP.nullPtr :: FP.Ptr Device)
gvalueSet_ Ptr GValue
gv (P.Just Device
obj) = Device -> (Ptr Device -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Device
obj (Ptr GValue -> Ptr Device -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Device)
gvalueGet_ Ptr GValue
gv = do
Ptr Device
ptr <- Ptr GValue -> IO (Ptr Device)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Device)
if Ptr Device
ptr Ptr Device -> Ptr Device -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Device
forall a. Ptr a
FP.nullPtr
then Device -> Maybe Device
forall a. a -> Maybe a
P.Just (Device -> Maybe Device) -> IO Device -> IO (Maybe Device)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Device -> Device
Device Ptr Device
ptr
else Maybe Device -> IO (Maybe Device)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Device
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceMethod (t :: Symbol) (o :: *) :: * where
ResolveDeviceMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
ResolveDeviceMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDeviceMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDeviceMethod "createElement" o = DeviceCreateElementMethodInfo
ResolveDeviceMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
ResolveDeviceMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDeviceMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDeviceMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDeviceMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
ResolveDeviceMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
ResolveDeviceMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
ResolveDeviceMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
ResolveDeviceMethod "hasClasses" o = DeviceHasClassesMethodInfo
ResolveDeviceMethod "hasClassesv" o = DeviceHasClassesvMethodInfo
ResolveDeviceMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDeviceMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDeviceMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDeviceMethod "reconfigureElement" o = DeviceReconfigureElementMethodInfo
ResolveDeviceMethod "ref" o = Gst.Object.ObjectRefMethodInfo
ResolveDeviceMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDeviceMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
ResolveDeviceMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDeviceMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDeviceMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDeviceMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
ResolveDeviceMethod "syncValues" o = Gst.Object.ObjectSyncValuesMethodInfo
ResolveDeviceMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDeviceMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
ResolveDeviceMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
ResolveDeviceMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDeviceMethod "getCaps" o = DeviceGetCapsMethodInfo
ResolveDeviceMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
ResolveDeviceMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
ResolveDeviceMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDeviceMethod "getDeviceClass" o = DeviceGetDeviceClassMethodInfo
ResolveDeviceMethod "getDisplayName" o = DeviceGetDisplayNameMethodInfo
ResolveDeviceMethod "getGValueArray" o = Gst.Object.ObjectGetGValueArrayMethodInfo
ResolveDeviceMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
ResolveDeviceMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
ResolveDeviceMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
ResolveDeviceMethod "getProperties" o = DeviceGetPropertiesMethodInfo
ResolveDeviceMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDeviceMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDeviceMethod "getValue" o = Gst.Object.ObjectGetValueMethodInfo
ResolveDeviceMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
ResolveDeviceMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
ResolveDeviceMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
ResolveDeviceMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDeviceMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDeviceMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
ResolveDeviceMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
ResolveDeviceMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDeviceMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDeviceMethod t Device, O.OverloadedMethod info Device p) => OL.IsLabel t (Device -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDeviceMethod t Device, O.OverloadedMethod info Device p, R.HasField t Device p) => R.HasField t Device p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDeviceMethod t Device, O.OverloadedMethodInfo info Device) => OL.IsLabel t (O.MethodProxy info Device) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type DeviceRemovedCallback =
IO ()
type C_DeviceRemovedCallback =
Ptr Device ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DeviceRemovedCallback :: C_DeviceRemovedCallback -> IO (FunPtr C_DeviceRemovedCallback)
wrap_DeviceRemovedCallback ::
GObject a => (a -> DeviceRemovedCallback) ->
C_DeviceRemovedCallback
wrap_DeviceRemovedCallback :: forall a. GObject a => (a -> IO ()) -> C_DeviceRemovedCallback
wrap_DeviceRemovedCallback a -> IO ()
gi'cb Ptr Device
gi'selfPtr Ptr ()
_ = do
Ptr Device -> (Device -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Device
gi'selfPtr ((Device -> IO ()) -> IO ()) -> (Device -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Device
gi'self -> a -> IO ()
gi'cb (Device -> a
Coerce.coerce Device
gi'self)
onDeviceRemoved :: (IsDevice a, MonadIO m) => a -> ((?self :: a) => DeviceRemovedCallback) -> m SignalHandlerId
onDeviceRemoved :: forall a (m :: * -> *).
(IsDevice a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDeviceRemoved a
obj (?self::a) => 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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DeviceRemovedCallback
wrapped' = (a -> IO ()) -> C_DeviceRemovedCallback
forall a. GObject a => (a -> IO ()) -> C_DeviceRemovedCallback
wrap_DeviceRemovedCallback a -> IO ()
wrapped
FunPtr C_DeviceRemovedCallback
wrapped'' <- C_DeviceRemovedCallback -> IO (FunPtr C_DeviceRemovedCallback)
mk_DeviceRemovedCallback C_DeviceRemovedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceRemovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"removed" FunPtr C_DeviceRemovedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDeviceRemoved :: (IsDevice a, MonadIO m) => a -> ((?self :: a) => DeviceRemovedCallback) -> m SignalHandlerId
afterDeviceRemoved :: forall a (m :: * -> *).
(IsDevice a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDeviceRemoved a
obj (?self::a) => 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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DeviceRemovedCallback
wrapped' = (a -> IO ()) -> C_DeviceRemovedCallback
forall a. GObject a => (a -> IO ()) -> C_DeviceRemovedCallback
wrap_DeviceRemovedCallback a -> IO ()
wrapped
FunPtr C_DeviceRemovedCallback
wrapped'' <- C_DeviceRemovedCallback -> IO (FunPtr C_DeviceRemovedCallback)
mk_DeviceRemovedCallback C_DeviceRemovedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceRemovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"removed" FunPtr C_DeviceRemovedCallback
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device::removed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#g:signal:removed"})
#endif
getDeviceCaps :: (MonadIO m, IsDevice o) => o -> m (Maybe Gst.Caps.Caps)
getDeviceCaps :: forall (m :: * -> *) o.
(MonadIO m, IsDevice o) =>
o -> m (Maybe Caps)
getDeviceCaps o
obj = IO (Maybe Caps) -> m (Maybe Caps)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Caps) -> m (Maybe Caps))
-> IO (Maybe Caps) -> m (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Caps -> Caps) -> IO (Maybe Caps)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"caps" ManagedPtr Caps -> Caps
Gst.Caps.Caps
constructDeviceCaps :: (IsDevice o, MIO.MonadIO m) => Gst.Caps.Caps -> m (GValueConstruct o)
constructDeviceCaps :: forall o (m :: * -> *).
(IsDevice o, MonadIO m) =>
Caps -> m (GValueConstruct o)
constructDeviceCaps Caps
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Caps -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"caps" (Caps -> Maybe Caps
forall a. a -> Maybe a
P.Just Caps
val)
#if defined(ENABLE_OVERLOADING)
data DeviceCapsPropertyInfo
instance AttrInfo DeviceCapsPropertyInfo where
type AttrAllowedOps DeviceCapsPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceCapsPropertyInfo = IsDevice
type AttrSetTypeConstraint DeviceCapsPropertyInfo = (~) Gst.Caps.Caps
type AttrTransferTypeConstraint DeviceCapsPropertyInfo = (~) Gst.Caps.Caps
type AttrTransferType DeviceCapsPropertyInfo = Gst.Caps.Caps
type AttrGetType DeviceCapsPropertyInfo = (Maybe Gst.Caps.Caps)
type AttrLabel DeviceCapsPropertyInfo = "caps"
type AttrOrigin DeviceCapsPropertyInfo = Device
attrGet = getDeviceCaps
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructDeviceCaps
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.caps"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#g:attr:caps"
})
#endif
getDeviceDeviceClass :: (MonadIO m, IsDevice o) => o -> m (Maybe T.Text)
getDeviceDeviceClass :: forall (m :: * -> *) o.
(MonadIO m, IsDevice o) =>
o -> m (Maybe Text)
getDeviceDeviceClass o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"device-class"
constructDeviceDeviceClass :: (IsDevice o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDeviceDeviceClass :: forall o (m :: * -> *).
(IsDevice o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDeviceDeviceClass Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"device-class" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data DeviceDeviceClassPropertyInfo
instance AttrInfo DeviceDeviceClassPropertyInfo where
type AttrAllowedOps DeviceDeviceClassPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceDeviceClassPropertyInfo = IsDevice
type AttrSetTypeConstraint DeviceDeviceClassPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint DeviceDeviceClassPropertyInfo = (~) T.Text
type AttrTransferType DeviceDeviceClassPropertyInfo = T.Text
type AttrGetType DeviceDeviceClassPropertyInfo = (Maybe T.Text)
type AttrLabel DeviceDeviceClassPropertyInfo = "device-class"
type AttrOrigin DeviceDeviceClassPropertyInfo = Device
attrGet = getDeviceDeviceClass
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructDeviceDeviceClass
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceClass"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#g:attr:deviceClass"
})
#endif
getDeviceDisplayName :: (MonadIO m, IsDevice o) => o -> m (Maybe T.Text)
getDeviceDisplayName :: forall (m :: * -> *) o.
(MonadIO m, IsDevice o) =>
o -> m (Maybe Text)
getDeviceDisplayName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"display-name"
constructDeviceDisplayName :: (IsDevice o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDeviceDisplayName :: forall o (m :: * -> *).
(IsDevice o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDeviceDisplayName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"display-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data DeviceDisplayNamePropertyInfo
instance AttrInfo DeviceDisplayNamePropertyInfo where
type AttrAllowedOps DeviceDisplayNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceDisplayNamePropertyInfo = IsDevice
type AttrSetTypeConstraint DeviceDisplayNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint DeviceDisplayNamePropertyInfo = (~) T.Text
type AttrTransferType DeviceDisplayNamePropertyInfo = T.Text
type AttrGetType DeviceDisplayNamePropertyInfo = (Maybe T.Text)
type AttrLabel DeviceDisplayNamePropertyInfo = "display-name"
type AttrOrigin DeviceDisplayNamePropertyInfo = Device
attrGet = getDeviceDisplayName
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructDeviceDisplayName
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.displayName"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#g:attr:displayName"
})
#endif
getDeviceProperties :: (MonadIO m, IsDevice o) => o -> m (Maybe Gst.Structure.Structure)
getDeviceProperties :: forall (m :: * -> *) o.
(MonadIO m, IsDevice o) =>
o -> m (Maybe Structure)
getDeviceProperties o
obj = IO (Maybe Structure) -> m (Maybe Structure)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Structure) -> m (Maybe Structure))
-> IO (Maybe Structure) -> m (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Structure -> Structure)
-> IO (Maybe Structure)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"properties" ManagedPtr Structure -> Structure
Gst.Structure.Structure
constructDeviceProperties :: (IsDevice o, MIO.MonadIO m) => Gst.Structure.Structure -> m (GValueConstruct o)
constructDeviceProperties :: forall o (m :: * -> *).
(IsDevice o, MonadIO m) =>
Structure -> m (GValueConstruct o)
constructDeviceProperties Structure
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Structure -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"properties" (Structure -> Maybe Structure
forall a. a -> Maybe a
P.Just Structure
val)
#if defined(ENABLE_OVERLOADING)
data DevicePropertiesPropertyInfo
instance AttrInfo DevicePropertiesPropertyInfo where
type AttrAllowedOps DevicePropertiesPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DevicePropertiesPropertyInfo = IsDevice
type AttrSetTypeConstraint DevicePropertiesPropertyInfo = (~) Gst.Structure.Structure
type AttrTransferTypeConstraint DevicePropertiesPropertyInfo = (~) Gst.Structure.Structure
type AttrTransferType DevicePropertiesPropertyInfo = Gst.Structure.Structure
type AttrGetType DevicePropertiesPropertyInfo = (Maybe Gst.Structure.Structure)
type AttrLabel DevicePropertiesPropertyInfo = "properties"
type AttrOrigin DevicePropertiesPropertyInfo = Device
attrGet = getDeviceProperties
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructDeviceProperties
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.properties"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#g:attr:properties"
})
#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
foreign import ccall "gst_device_create_element" gst_device_create_element ::
Ptr Device ->
CString ->
IO (Ptr Gst.Element.Element)
deviceCreateElement ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> Maybe (T.Text)
-> m (Maybe Gst.Element.Element)
deviceCreateElement :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> Maybe Text -> m (Maybe Element)
deviceCreateElement a
device Maybe Text
name = IO (Maybe Element) -> m (Maybe Element)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Element) -> m (Maybe Element))
-> IO (Maybe Element) -> m (Maybe Element)
forall a b. (a -> b) -> a -> b
$ do
Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr CChar
maybeName <- case Maybe Text
name of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jName -> do
Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
Ptr Element
result <- Ptr Device -> Ptr CChar -> IO (Ptr Element)
gst_device_create_element Ptr Device
device' Ptr CChar
maybeName
Maybe Element
maybeResult <- Ptr Element -> (Ptr Element -> IO Element) -> IO (Maybe Element)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Element
result ((Ptr Element -> IO Element) -> IO (Maybe Element))
-> (Ptr Element -> IO Element) -> IO (Maybe Element)
forall a b. (a -> b) -> a -> b
$ \Ptr Element
result' -> do
Element
result'' <- ((ManagedPtr Element -> Element) -> Ptr Element -> IO Element
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Element -> Element
Gst.Element.Element) Ptr Element
result'
Element -> IO Element
forall (m :: * -> *) a. Monad m => a -> m a
return Element
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
Maybe Element -> IO (Maybe Element)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Element
maybeResult
#if defined(ENABLE_OVERLOADING)
data DeviceCreateElementMethodInfo
instance (signature ~ (Maybe (T.Text) -> m (Maybe Gst.Element.Element)), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceCreateElementMethodInfo a signature where
overloadedMethod = deviceCreateElement
instance O.OverloadedMethodInfo DeviceCreateElementMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceCreateElement",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#v:deviceCreateElement"
})
#endif
foreign import ccall "gst_device_get_caps" gst_device_get_caps ::
Ptr Device ->
IO (Ptr Gst.Caps.Caps)
deviceGetCaps ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m (Maybe Gst.Caps.Caps)
deviceGetCaps :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> m (Maybe Caps)
deviceGetCaps a
device = IO (Maybe Caps) -> m (Maybe Caps)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Caps) -> m (Maybe Caps))
-> IO (Maybe Caps) -> m (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ do
Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr Caps
result <- Ptr Device -> IO (Ptr Caps)
gst_device_get_caps Ptr Device
device'
Maybe Caps
maybeResult <- Ptr Caps -> (Ptr Caps -> IO Caps) -> IO (Maybe Caps)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Caps
result ((Ptr Caps -> IO Caps) -> IO (Maybe Caps))
-> (Ptr Caps -> IO Caps) -> IO (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ \Ptr Caps
result' -> do
Caps
result'' <- ((ManagedPtr Caps -> Caps) -> Ptr Caps -> IO Caps
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Caps -> Caps
Gst.Caps.Caps) Ptr Caps
result'
Caps -> IO Caps
forall (m :: * -> *) a. Monad m => a -> m a
return Caps
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Maybe Caps -> IO (Maybe Caps)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Caps
maybeResult
#if defined(ENABLE_OVERLOADING)
data DeviceGetCapsMethodInfo
instance (signature ~ (m (Maybe Gst.Caps.Caps)), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceGetCapsMethodInfo a signature where
overloadedMethod = deviceGetCaps
instance O.OverloadedMethodInfo DeviceGetCapsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceGetCaps",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#v:deviceGetCaps"
})
#endif
foreign import ccall "gst_device_get_device_class" gst_device_get_device_class ::
Ptr Device ->
IO CString
deviceGetDeviceClass ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m T.Text
deviceGetDeviceClass :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> m Text
deviceGetDeviceClass a
device = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr CChar
result <- Ptr Device -> IO (Ptr CChar)
gst_device_get_device_class Ptr Device
device'
Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceGetDeviceClass" Ptr CChar
result
Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DeviceGetDeviceClassMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceGetDeviceClassMethodInfo a signature where
overloadedMethod = deviceGetDeviceClass
instance O.OverloadedMethodInfo DeviceGetDeviceClassMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceGetDeviceClass",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#v:deviceGetDeviceClass"
})
#endif
foreign import ccall "gst_device_get_display_name" gst_device_get_display_name ::
Ptr Device ->
IO CString
deviceGetDisplayName ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m T.Text
deviceGetDisplayName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> m Text
deviceGetDisplayName a
device = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr CChar
result <- Ptr Device -> IO (Ptr CChar)
gst_device_get_display_name Ptr Device
device'
Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceGetDisplayName" Ptr CChar
result
Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DeviceGetDisplayNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceGetDisplayNameMethodInfo a signature where
overloadedMethod = deviceGetDisplayName
instance O.OverloadedMethodInfo DeviceGetDisplayNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceGetDisplayName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#v:deviceGetDisplayName"
})
#endif
foreign import ccall "gst_device_get_properties" gst_device_get_properties ::
Ptr Device ->
IO (Ptr Gst.Structure.Structure)
deviceGetProperties ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m (Maybe Gst.Structure.Structure)
deviceGetProperties :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> m (Maybe Structure)
deviceGetProperties a
device = IO (Maybe Structure) -> m (Maybe Structure)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Structure) -> m (Maybe Structure))
-> IO (Maybe Structure) -> m (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ do
Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr Structure
result <- Ptr Device -> IO (Ptr Structure)
gst_device_get_properties Ptr Device
device'
Maybe Structure
maybeResult <- Ptr Structure
-> (Ptr Structure -> IO Structure) -> IO (Maybe Structure)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Structure
result ((Ptr Structure -> IO Structure) -> IO (Maybe Structure))
-> (Ptr Structure -> IO Structure) -> IO (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ \Ptr Structure
result' -> do
Structure
result'' <- ((ManagedPtr Structure -> Structure)
-> Ptr Structure -> IO Structure
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Structure -> Structure
Gst.Structure.Structure) Ptr Structure
result'
Structure -> IO Structure
forall (m :: * -> *) a. Monad m => a -> m a
return Structure
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Maybe Structure -> IO (Maybe Structure)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Structure
maybeResult
#if defined(ENABLE_OVERLOADING)
data DeviceGetPropertiesMethodInfo
instance (signature ~ (m (Maybe Gst.Structure.Structure)), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceGetPropertiesMethodInfo a signature where
overloadedMethod = deviceGetProperties
instance O.OverloadedMethodInfo DeviceGetPropertiesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceGetProperties",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#v:deviceGetProperties"
})
#endif
foreign import ccall "gst_device_has_classes" gst_device_has_classes ::
Ptr Device ->
CString ->
IO CInt
deviceHasClasses ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> T.Text
-> m Bool
deviceHasClasses :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> Text -> m Bool
deviceHasClasses a
device Text
classes = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr CChar
classes' <- Text -> IO (Ptr CChar)
textToCString Text
classes
CInt
result <- Ptr Device -> Ptr CChar -> IO CInt
gst_device_has_classes Ptr Device
device' Ptr CChar
classes'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
classes'
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceHasClassesMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceHasClassesMethodInfo a signature where
overloadedMethod = deviceHasClasses
instance O.OverloadedMethodInfo DeviceHasClassesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceHasClasses",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#v:deviceHasClasses"
})
#endif
foreign import ccall "gst_device_has_classesv" gst_device_has_classesv ::
Ptr Device ->
Ptr CString ->
IO CInt
deviceHasClassesv ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> [T.Text]
-> m Bool
deviceHasClassesv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDevice a) =>
a -> [Text] -> m Bool
deviceHasClassesv a
device [Text]
classes = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr (Ptr CChar)
classes' <- [Text] -> IO (Ptr (Ptr CChar))
packZeroTerminatedUTF8CArray [Text]
classes
CInt
result <- Ptr Device -> Ptr (Ptr CChar) -> IO CInt
gst_device_has_classesv Ptr Device
device' Ptr (Ptr CChar)
classes'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
(Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
classes'
Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
classes'
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceHasClassesvMethodInfo
instance (signature ~ ([T.Text] -> m Bool), MonadIO m, IsDevice a) => O.OverloadedMethod DeviceHasClassesvMethodInfo a signature where
overloadedMethod = deviceHasClassesv
instance O.OverloadedMethodInfo DeviceHasClassesvMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceHasClassesv",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#v:deviceHasClassesv"
})
#endif
foreign import ccall "gst_device_reconfigure_element" gst_device_reconfigure_element ::
Ptr Device ->
Ptr Gst.Element.Element ->
IO CInt
deviceReconfigureElement ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a, Gst.Element.IsElement b) =>
a
-> b
-> m Bool
deviceReconfigureElement :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDevice a, IsElement b) =>
a -> b -> m Bool
deviceReconfigureElement a
device b
element = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr Element
element' <- b -> IO (Ptr Element)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
element
CInt
result <- Ptr Device -> Ptr Element -> IO CInt
gst_device_reconfigure_element Ptr Device
device' Ptr Element
element'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
element
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceReconfigureElementMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDevice a, Gst.Element.IsElement b) => O.OverloadedMethod DeviceReconfigureElementMethodInfo a signature where
overloadedMethod = deviceReconfigureElement
instance O.OverloadedMethodInfo DeviceReconfigureElementMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Objects.Device.deviceReconfigureElement",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.25/docs/GI-Gst-Objects-Device.html#v:deviceReconfigureElement"
})
#endif