{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gst.Objects.ElementFactory.ElementFactory' is used to create instances of elements. A
-- GstElementFactory can be added to a t'GI.Gst.Objects.Plugin.Plugin' as it is also a
-- t'GI.Gst.Objects.PluginFeature.PluginFeature'.
-- 
-- Use the 'GI.Gst.Objects.ElementFactory.elementFactoryFind' and 'GI.Gst.Objects.ElementFactory.elementFactoryCreate'
-- functions to create element instances or use 'GI.Gst.Objects.ElementFactory.elementFactoryMake' as a
-- convenient shortcut.
-- 
-- The following code example shows you how to create a GstFileSrc element.
-- 
-- == Using an element factory
-- 
-- === /C code/
-- >
-- >  #include <gst/gst.h>
-- >
-- >  GstElement *src;
-- >  GstElementFactory *srcfactory;
-- >
-- >  gst_init (&argc, &argv);
-- >
-- >  srcfactory = gst_element_factory_find ("filesrc");
-- >  g_return_if_fail (srcfactory != NULL);
-- >  src = gst_element_factory_create (srcfactory, "src");
-- >  g_return_if_fail (src != NULL);
-- >  ...
-- 

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

module GI.Gst.Objects.ElementFactory
    ( 

-- * Exported types
    ElementFactory(..)                      ,
    IsElementFactory                        ,
    toElementFactory                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveElementFactoryMethod             ,
#endif


-- ** canSinkAllCaps #method:canSinkAllCaps#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryCanSinkAllCapsMethodInfo  ,
#endif
    elementFactoryCanSinkAllCaps            ,


-- ** canSinkAnyCaps #method:canSinkAnyCaps#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryCanSinkAnyCapsMethodInfo  ,
#endif
    elementFactoryCanSinkAnyCaps            ,


-- ** canSrcAllCaps #method:canSrcAllCaps#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryCanSrcAllCapsMethodInfo   ,
#endif
    elementFactoryCanSrcAllCaps             ,


-- ** canSrcAnyCaps #method:canSrcAnyCaps#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryCanSrcAnyCapsMethodInfo   ,
#endif
    elementFactoryCanSrcAnyCaps             ,


-- ** create #method:create#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryCreateMethodInfo          ,
#endif
    elementFactoryCreate                    ,


-- ** find #method:find#

    elementFactoryFind                      ,


-- ** getElementType #method:getElementType#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetElementTypeMethodInfo  ,
#endif
    elementFactoryGetElementType            ,


-- ** getMetadata #method:getMetadata#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetMetadataMethodInfo     ,
#endif
    elementFactoryGetMetadata               ,


-- ** getMetadataKeys #method:getMetadataKeys#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetMetadataKeysMethodInfo ,
#endif
    elementFactoryGetMetadataKeys           ,


-- ** getNumPadTemplates #method:getNumPadTemplates#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetNumPadTemplatesMethodInfo,
#endif
    elementFactoryGetNumPadTemplates        ,


-- ** getStaticPadTemplates #method:getStaticPadTemplates#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetStaticPadTemplatesMethodInfo,
#endif
    elementFactoryGetStaticPadTemplates     ,


-- ** getUriProtocols #method:getUriProtocols#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetUriProtocolsMethodInfo ,
#endif
    elementFactoryGetUriProtocols           ,


-- ** getUriType #method:getUriType#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetUriTypeMethodInfo      ,
#endif
    elementFactoryGetUriType                ,


-- ** hasInterface #method:hasInterface#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryHasInterfaceMethodInfo    ,
#endif
    elementFactoryHasInterface              ,


-- ** listFilter #method:listFilter#

    elementFactoryListFilter                ,


-- ** listGetElements #method:listGetElements#

    elementFactoryListGetElements           ,


-- ** listIsType #method:listIsType#

#if defined(ENABLE_OVERLOADING)
    ElementFactoryListIsTypeMethodInfo      ,
#endif
    elementFactoryListIsType                ,


-- ** make #method:make#

    elementFactoryMake                      ,




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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gst.Enums as Gst.Enums
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.Objects.PluginFeature as Gst.PluginFeature
import {-# SOURCE #-} qualified GI.Gst.Structs.Caps as Gst.Caps
import {-# SOURCE #-} qualified GI.Gst.Structs.StaticPadTemplate as Gst.StaticPadTemplate

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

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

foreign import ccall "gst_element_factory_get_type"
    c_gst_element_factory_get_type :: IO B.Types.GType

instance B.Types.TypedObject ElementFactory where
    glibType :: IO GType
glibType = IO GType
c_gst_element_factory_get_type

instance B.Types.GObject ElementFactory

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveElementFactoryMethod (t :: Symbol) (o :: *) :: * where
    ResolveElementFactoryMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
    ResolveElementFactoryMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveElementFactoryMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveElementFactoryMethod "canSinkAllCaps" o = ElementFactoryCanSinkAllCapsMethodInfo
    ResolveElementFactoryMethod "canSinkAnyCaps" o = ElementFactoryCanSinkAnyCapsMethodInfo
    ResolveElementFactoryMethod "canSrcAllCaps" o = ElementFactoryCanSrcAllCapsMethodInfo
    ResolveElementFactoryMethod "canSrcAnyCaps" o = ElementFactoryCanSrcAnyCapsMethodInfo
    ResolveElementFactoryMethod "checkVersion" o = Gst.PluginFeature.PluginFeatureCheckVersionMethodInfo
    ResolveElementFactoryMethod "create" o = ElementFactoryCreateMethodInfo
    ResolveElementFactoryMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
    ResolveElementFactoryMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveElementFactoryMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveElementFactoryMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveElementFactoryMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
    ResolveElementFactoryMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
    ResolveElementFactoryMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
    ResolveElementFactoryMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
    ResolveElementFactoryMethod "hasInterface" o = ElementFactoryHasInterfaceMethodInfo
    ResolveElementFactoryMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveElementFactoryMethod "listIsType" o = ElementFactoryListIsTypeMethodInfo
    ResolveElementFactoryMethod "load" o = Gst.PluginFeature.PluginFeatureLoadMethodInfo
    ResolveElementFactoryMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveElementFactoryMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveElementFactoryMethod "ref" o = Gst.Object.ObjectRefMethodInfo
    ResolveElementFactoryMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveElementFactoryMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
    ResolveElementFactoryMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveElementFactoryMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveElementFactoryMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveElementFactoryMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
    ResolveElementFactoryMethod "syncValues" o = Gst.Object.ObjectSyncValuesMethodInfo
    ResolveElementFactoryMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveElementFactoryMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
    ResolveElementFactoryMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
    ResolveElementFactoryMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveElementFactoryMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
    ResolveElementFactoryMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
    ResolveElementFactoryMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveElementFactoryMethod "getElementType" o = ElementFactoryGetElementTypeMethodInfo
    ResolveElementFactoryMethod "getGValueArray" o = Gst.Object.ObjectGetGValueArrayMethodInfo
    ResolveElementFactoryMethod "getMetadata" o = ElementFactoryGetMetadataMethodInfo
    ResolveElementFactoryMethod "getMetadataKeys" o = ElementFactoryGetMetadataKeysMethodInfo
    ResolveElementFactoryMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
    ResolveElementFactoryMethod "getNumPadTemplates" o = ElementFactoryGetNumPadTemplatesMethodInfo
    ResolveElementFactoryMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
    ResolveElementFactoryMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
    ResolveElementFactoryMethod "getPlugin" o = Gst.PluginFeature.PluginFeatureGetPluginMethodInfo
    ResolveElementFactoryMethod "getPluginName" o = Gst.PluginFeature.PluginFeatureGetPluginNameMethodInfo
    ResolveElementFactoryMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveElementFactoryMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveElementFactoryMethod "getRank" o = Gst.PluginFeature.PluginFeatureGetRankMethodInfo
    ResolveElementFactoryMethod "getStaticPadTemplates" o = ElementFactoryGetStaticPadTemplatesMethodInfo
    ResolveElementFactoryMethod "getUriProtocols" o = ElementFactoryGetUriProtocolsMethodInfo
    ResolveElementFactoryMethod "getUriType" o = ElementFactoryGetUriTypeMethodInfo
    ResolveElementFactoryMethod "getValue" o = Gst.Object.ObjectGetValueMethodInfo
    ResolveElementFactoryMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
    ResolveElementFactoryMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
    ResolveElementFactoryMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
    ResolveElementFactoryMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveElementFactoryMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveElementFactoryMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
    ResolveElementFactoryMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
    ResolveElementFactoryMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveElementFactoryMethod "setRank" o = Gst.PluginFeature.PluginFeatureSetRankMethodInfo
    ResolveElementFactoryMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method ElementFactory::can_sink_all_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "factory to query" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the caps to check" , 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_element_factory_can_sink_all_caps" gst_element_factory_can_sink_all_caps :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO CInt

-- | Checks if the factory can sink all possible capabilities.
elementFactoryCanSinkAllCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: factory to query
    -> Gst.Caps.Caps
    -- ^ /@caps@/: the caps to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the caps are fully compatible.
elementFactoryCanSinkAllCaps :: a -> Caps -> m Bool
elementFactoryCanSinkAllCaps a
factory Caps
caps = 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr Caps
caps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
caps
    CInt
result <- Ptr ElementFactory -> Ptr Caps -> IO CInt
gst_element_factory_can_sink_all_caps Ptr ElementFactory
factory' Ptr Caps
caps'
    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
factory
    Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Caps
caps
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ElementFactoryCanSinkAllCapsMethodInfo
instance (signature ~ (Gst.Caps.Caps -> m Bool), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryCanSinkAllCapsMethodInfo a signature where
    overloadedMethod = elementFactoryCanSinkAllCaps

#endif

-- method ElementFactory::can_sink_any_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "factory to query" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the caps to check" , 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_element_factory_can_sink_any_caps" gst_element_factory_can_sink_any_caps :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO CInt

-- | Checks if the factory can sink any possible capability.
elementFactoryCanSinkAnyCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: factory to query
    -> Gst.Caps.Caps
    -- ^ /@caps@/: the caps to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the caps have a common subset.
elementFactoryCanSinkAnyCaps :: a -> Caps -> m Bool
elementFactoryCanSinkAnyCaps a
factory Caps
caps = 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr Caps
caps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
caps
    CInt
result <- Ptr ElementFactory -> Ptr Caps -> IO CInt
gst_element_factory_can_sink_any_caps Ptr ElementFactory
factory' Ptr Caps
caps'
    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
factory
    Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Caps
caps
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ElementFactoryCanSinkAnyCapsMethodInfo
instance (signature ~ (Gst.Caps.Caps -> m Bool), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryCanSinkAnyCapsMethodInfo a signature where
    overloadedMethod = elementFactoryCanSinkAnyCaps

#endif

-- method ElementFactory::can_src_all_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "factory to query" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the caps to check" , 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_element_factory_can_src_all_caps" gst_element_factory_can_src_all_caps :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO CInt

-- | Checks if the factory can src all possible capabilities.
elementFactoryCanSrcAllCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: factory to query
    -> Gst.Caps.Caps
    -- ^ /@caps@/: the caps to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the caps are fully compatible.
elementFactoryCanSrcAllCaps :: a -> Caps -> m Bool
elementFactoryCanSrcAllCaps a
factory Caps
caps = 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr Caps
caps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
caps
    CInt
result <- Ptr ElementFactory -> Ptr Caps -> IO CInt
gst_element_factory_can_src_all_caps Ptr ElementFactory
factory' Ptr Caps
caps'
    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
factory
    Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Caps
caps
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ElementFactoryCanSrcAllCapsMethodInfo
instance (signature ~ (Gst.Caps.Caps -> m Bool), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryCanSrcAllCapsMethodInfo a signature where
    overloadedMethod = elementFactoryCanSrcAllCaps

#endif

-- method ElementFactory::can_src_any_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "factory to query" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the caps to check" , 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_element_factory_can_src_any_caps" gst_element_factory_can_src_any_caps :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO CInt

-- | Checks if the factory can src any possible capability.
elementFactoryCanSrcAnyCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: factory to query
    -> Gst.Caps.Caps
    -- ^ /@caps@/: the caps to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the caps have a common subset.
elementFactoryCanSrcAnyCaps :: a -> Caps -> m Bool
elementFactoryCanSrcAnyCaps a
factory Caps
caps = 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr Caps
caps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
caps
    CInt
result <- Ptr ElementFactory -> Ptr Caps -> IO CInt
gst_element_factory_can_src_any_caps Ptr ElementFactory
factory' Ptr Caps
caps'
    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
factory
    Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Caps
caps
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ElementFactoryCanSrcAnyCapsMethodInfo
instance (signature ~ (Gst.Caps.Caps -> m Bool), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryCanSrcAnyCapsMethodInfo a signature where
    overloadedMethod = elementFactoryCanSrcAnyCaps

#endif

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

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

-- | Create a new element of the type defined by the given elementfactory.
-- It will be given the name supplied, since all elements require a name as
-- their first argument.
elementFactoryCreate ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: factory to instantiate
    -> Maybe (T.Text)
    -- ^ /@name@/: name of new element, or 'P.Nothing' to automatically create
    --    a unique name
    -> m (Maybe Gst.Element.Element)
    -- ^ __Returns:__ new t'GI.Gst.Objects.Element.Element' or 'P.Nothing'
    --     if the element couldn\'t be created
elementFactoryCreate :: a -> Maybe Text -> m (Maybe Element)
elementFactoryCreate a
factory 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    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 ElementFactory -> Ptr CChar -> IO (Ptr Element)
gst_element_factory_create Ptr ElementFactory
factory' 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
factory
    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 ElementFactoryCreateMethodInfo
instance (signature ~ (Maybe (T.Text) -> m (Maybe Gst.Element.Element)), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryCreateMethodInfo a signature where
    overloadedMethod = elementFactoryCreate

#endif

-- method ElementFactory::get_element_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "factory to get managed #GType from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "gst_element_factory_get_element_type" gst_element_factory_get_element_type :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    IO CGType

-- | Get the t'GType' for elements managed by this factory. The type can
-- only be retrieved if the element factory is loaded, which can be
-- assured with 'GI.Gst.Objects.PluginFeature.pluginFeatureLoad'.
elementFactoryGetElementType ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: factory to get managed t'GType' from
    -> m GType
    -- ^ __Returns:__ the t'GType' for elements managed by this factory or 0 if
    -- the factory is not loaded.
elementFactoryGetElementType :: a -> m GType
elementFactoryGetElementType a
factory = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    Ptr ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    CGType
result <- Ptr ElementFactory -> IO CGType
gst_element_factory_get_element_type Ptr ElementFactory
factory'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
data ElementFactoryGetElementTypeMethodInfo
instance (signature ~ (m GType), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryGetElementTypeMethodInfo a signature where
    overloadedMethod = elementFactoryGetElementType

#endif

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

foreign import ccall "gst_element_factory_get_metadata" gst_element_factory_get_metadata :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    CString ->                              -- key : TBasicType TUTF8
    IO CString

-- | Get the metadata on /@factory@/ with /@key@/.
elementFactoryGetMetadata ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: a t'GI.Gst.Objects.ElementFactory.ElementFactory'
    -> T.Text
    -- ^ /@key@/: a key
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the metadata with /@key@/ on /@factory@/ or 'P.Nothing'
    -- when there was no metadata with the given /@key@/.
elementFactoryGetMetadata :: a -> Text -> m (Maybe Text)
elementFactoryGetMetadata a
factory Text
key = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr CChar
key' <- Text -> IO (Ptr CChar)
textToCString Text
key
    Ptr CChar
result <- Ptr ElementFactory -> Ptr CChar -> IO (Ptr CChar)
gst_element_factory_get_metadata Ptr ElementFactory
factory' Ptr CChar
key'
    Maybe Text
maybeResult <- Ptr CChar -> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CChar
result ((Ptr CChar -> IO Text) -> IO (Maybe Text))
-> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
result' -> do
        Text
result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
key'
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ElementFactoryGetMetadataMethodInfo
instance (signature ~ (T.Text -> m (Maybe T.Text)), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryGetMetadataMethodInfo a signature where
    overloadedMethod = elementFactoryGetMetadata

#endif

-- method ElementFactory::get_metadata_keys
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstElementFactory"
--                 , 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_element_factory_get_metadata_keys" gst_element_factory_get_metadata_keys :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    IO (Ptr CString)

-- | Get the available keys for the metadata on /@factory@/.
elementFactoryGetMetadataKeys ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: a t'GI.Gst.Objects.ElementFactory.ElementFactory'
    -> m (Maybe [T.Text])
    -- ^ __Returns:__ 
    -- a 'P.Nothing'-terminated array of key strings, or 'P.Nothing' when there is no
    -- metadata. Free with 'GI.GLib.Functions.strfreev' when no longer needed.
elementFactoryGetMetadataKeys :: a -> m (Maybe [Text])
elementFactoryGetMetadataKeys a
factory = IO (Maybe [Text]) -> m (Maybe [Text])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ do
    Ptr ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr (Ptr CChar)
result <- Ptr ElementFactory -> IO (Ptr (Ptr CChar))
gst_element_factory_get_metadata_keys Ptr ElementFactory
factory'
    Maybe [Text]
maybeResult <- Ptr (Ptr CChar)
-> (Ptr (Ptr CChar) -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr (Ptr CChar)
result ((Ptr (Ptr CChar) -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr (Ptr CChar) -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CChar)
result' -> do
        [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'
        [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    Maybe [Text] -> IO (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult

#if defined(ENABLE_OVERLOADING)
data ElementFactoryGetMetadataKeysMethodInfo
instance (signature ~ (m (Maybe [T.Text])), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryGetMetadataKeysMethodInfo a signature where
    overloadedMethod = elementFactoryGetMetadataKeys

#endif

-- method ElementFactory::get_num_pad_templates
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstElementFactory"
--                 , 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_element_factory_get_num_pad_templates" gst_element_factory_get_num_pad_templates :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    IO Word32

-- | Gets the number of pad_templates in this factory.
elementFactoryGetNumPadTemplates ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: a t'GI.Gst.Objects.ElementFactory.ElementFactory'
    -> m Word32
    -- ^ __Returns:__ the number of pad_templates
elementFactoryGetNumPadTemplates :: a -> m Word32
elementFactoryGetNumPadTemplates a
factory = 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Word32
result <- Ptr ElementFactory -> IO Word32
gst_element_factory_get_num_pad_templates Ptr ElementFactory
factory'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data ElementFactoryGetNumPadTemplatesMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryGetNumPadTemplatesMethodInfo a signature where
    overloadedMethod = elementFactoryGetNumPadTemplates

#endif

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

foreign import ccall "gst_element_factory_get_static_pad_templates" gst_element_factory_get_static_pad_templates :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    IO (Ptr (GList (Ptr Gst.StaticPadTemplate.StaticPadTemplate)))

-- | Gets the t'GI.GLib.Structs.List.List' of t'GI.Gst.Structs.StaticPadTemplate.StaticPadTemplate' for this factory.
elementFactoryGetStaticPadTemplates ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: a t'GI.Gst.Objects.ElementFactory.ElementFactory'
    -> m [Gst.StaticPadTemplate.StaticPadTemplate]
    -- ^ __Returns:__ the
    --     static pad templates
elementFactoryGetStaticPadTemplates :: a -> m [StaticPadTemplate]
elementFactoryGetStaticPadTemplates a
factory = IO [StaticPadTemplate] -> m [StaticPadTemplate]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [StaticPadTemplate] -> m [StaticPadTemplate])
-> IO [StaticPadTemplate] -> m [StaticPadTemplate]
forall a b. (a -> b) -> a -> b
$ do
    Ptr ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr (GList (Ptr StaticPadTemplate))
result <- Ptr ElementFactory -> IO (Ptr (GList (Ptr StaticPadTemplate)))
gst_element_factory_get_static_pad_templates Ptr ElementFactory
factory'
    [Ptr StaticPadTemplate]
result' <- Ptr (GList (Ptr StaticPadTemplate)) -> IO [Ptr StaticPadTemplate]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr StaticPadTemplate))
result
    [StaticPadTemplate]
result'' <- (Ptr StaticPadTemplate -> IO StaticPadTemplate)
-> [Ptr StaticPadTemplate] -> IO [StaticPadTemplate]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr StaticPadTemplate -> StaticPadTemplate)
-> Ptr StaticPadTemplate -> IO StaticPadTemplate
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr StaticPadTemplate -> StaticPadTemplate
Gst.StaticPadTemplate.StaticPadTemplate) [Ptr StaticPadTemplate]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    [StaticPadTemplate] -> IO [StaticPadTemplate]
forall (m :: * -> *) a. Monad m => a -> m a
return [StaticPadTemplate]
result''

#if defined(ENABLE_OVERLOADING)
data ElementFactoryGetStaticPadTemplatesMethodInfo
instance (signature ~ (m [Gst.StaticPadTemplate.StaticPadTemplate]), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryGetStaticPadTemplatesMethodInfo a signature where
    overloadedMethod = elementFactoryGetStaticPadTemplates

#endif

-- method ElementFactory::get_uri_protocols
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstElementFactory"
--                 , 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_element_factory_get_uri_protocols" gst_element_factory_get_uri_protocols :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    IO (Ptr CString)

-- | Gets a 'P.Nothing'-terminated array of protocols this element supports or 'P.Nothing' if
-- no protocols are supported. You may not change the contents of the returned
-- array, as it is still owned by the element factory. Use @/g_strdupv()/@ to
-- make a copy of the protocol string array if you need to.
elementFactoryGetUriProtocols ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: a t'GI.Gst.Objects.ElementFactory.ElementFactory'
    -> m [T.Text]
    -- ^ __Returns:__ the supported protocols
    --     or 'P.Nothing'
elementFactoryGetUriProtocols :: a -> m [Text]
elementFactoryGetUriProtocols a
factory = 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr (Ptr CChar)
result <- Ptr ElementFactory -> IO (Ptr (Ptr CChar))
gst_element_factory_get_uri_protocols Ptr ElementFactory
factory'
    Text -> Ptr (Ptr CChar) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"elementFactoryGetUriProtocols" Ptr (Ptr CChar)
result
    [Text]
result' <- HasCallStack => Ptr (Ptr CChar) -> IO [Text]
Ptr (Ptr CChar) -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr (Ptr CChar)
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

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

#endif

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

foreign import ccall "gst_element_factory_get_uri_type" gst_element_factory_get_uri_type :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    IO CUInt

-- | Gets the type of URIs the element supports or @/GST_URI_UNKNOWN/@ if none.
elementFactoryGetUriType ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: a t'GI.Gst.Objects.ElementFactory.ElementFactory'
    -> m Gst.Enums.URIType
    -- ^ __Returns:__ type of URIs this element supports
elementFactoryGetUriType :: a -> m URIType
elementFactoryGetUriType a
factory = IO URIType -> m URIType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO URIType -> m URIType) -> IO URIType -> m URIType
forall a b. (a -> b) -> a -> b
$ do
    Ptr ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    CUInt
result <- Ptr ElementFactory -> IO CUInt
gst_element_factory_get_uri_type Ptr ElementFactory
factory'
    let result' :: URIType
result' = (Int -> URIType
forall a. Enum a => Int -> a
toEnum (Int -> URIType) -> (CUInt -> Int) -> CUInt -> URIType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    URIType -> IO URIType
forall (m :: * -> *) a. Monad m => a -> m a
return URIType
result'

#if defined(ENABLE_OVERLOADING)
data ElementFactoryGetUriTypeMethodInfo
instance (signature ~ (m Gst.Enums.URIType), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryGetUriTypeMethodInfo a signature where
    overloadedMethod = elementFactoryGetUriType

#endif

-- method ElementFactory::has_interface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstElementFactory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interfacename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an interface name" , 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_element_factory_has_interface" gst_element_factory_has_interface :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    CString ->                              -- interfacename : TBasicType TUTF8
    IO CInt

-- | Check if /@factory@/ implements the interface with name /@interfacename@/.
elementFactoryHasInterface ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: a t'GI.Gst.Objects.ElementFactory.ElementFactory'
    -> T.Text
    -- ^ /@interfacename@/: an interface name
    -> m Bool
    -- ^ __Returns:__ 'P.True' when /@factory@/ implement the interface.
elementFactoryHasInterface :: a -> Text -> m Bool
elementFactoryHasInterface a
factory Text
interfacename = 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr CChar
interfacename' <- Text -> IO (Ptr CChar)
textToCString Text
interfacename
    CInt
result <- Ptr ElementFactory -> Ptr CChar -> IO CInt
gst_element_factory_has_interface Ptr ElementFactory
factory' Ptr CChar
interfacename'
    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
factory
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
interfacename'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ElementFactoryHasInterfaceMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryHasInterfaceMethodInfo a signature where
    overloadedMethod = elementFactoryHasInterface

#endif

-- method ElementFactory::list_is_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "ElementFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstElementFactory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstElementFactoryListType"
--                 , 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_element_factory_list_is_type" gst_element_factory_list_is_type :: 
    Ptr ElementFactory ->                   -- factory : TInterface (Name {namespace = "Gst", name = "ElementFactory"})
    Word64 ->                               -- type : TBasicType TUInt64
    IO CInt

-- | Check if /@factory@/ is of the given types.
elementFactoryListIsType ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    -- ^ /@factory@/: a t'GI.Gst.Objects.ElementFactory.ElementFactory'
    -> Word64
    -- ^ /@type@/: a @/GstElementFactoryListType/@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@factory@/ is of /@type@/.
elementFactoryListIsType :: a -> CGType -> m Bool
elementFactoryListIsType a
factory CGType
type_ = 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 ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    CInt
result <- Ptr ElementFactory -> CGType -> IO CInt
gst_element_factory_list_is_type Ptr ElementFactory
factory' CGType
type_
    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
factory
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ElementFactoryListIsTypeMethodInfo
instance (signature ~ (Word64 -> m Bool), MonadIO m, IsElementFactory a) => O.MethodInfo ElementFactoryListIsTypeMethodInfo a signature where
    overloadedMethod = elementFactoryListIsType

#endif

-- method ElementFactory::find
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of factory to find"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gst" , name = "ElementFactory" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_element_factory_find" gst_element_factory_find :: 
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr ElementFactory)

-- | Search for an element factory of the given name. Refs the returned
-- element factory; caller is responsible for unreffing.
elementFactoryFind ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: name of factory to find
    -> m (Maybe ElementFactory)
    -- ^ __Returns:__ t'GI.Gst.Objects.ElementFactory.ElementFactory' if found,
    -- 'P.Nothing' otherwise
elementFactoryFind :: Text -> m (Maybe ElementFactory)
elementFactoryFind Text
name = IO (Maybe ElementFactory) -> m (Maybe ElementFactory)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ElementFactory) -> m (Maybe ElementFactory))
-> IO (Maybe ElementFactory) -> m (Maybe ElementFactory)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
name' <- Text -> IO (Ptr CChar)
textToCString Text
name
    Ptr ElementFactory
result <- Ptr CChar -> IO (Ptr ElementFactory)
gst_element_factory_find Ptr CChar
name'
    Maybe ElementFactory
maybeResult <- Ptr ElementFactory
-> (Ptr ElementFactory -> IO ElementFactory)
-> IO (Maybe ElementFactory)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ElementFactory
result ((Ptr ElementFactory -> IO ElementFactory)
 -> IO (Maybe ElementFactory))
-> (Ptr ElementFactory -> IO ElementFactory)
-> IO (Maybe ElementFactory)
forall a b. (a -> b) -> a -> b
$ \Ptr ElementFactory
result' -> do
        ElementFactory
result'' <- ((ManagedPtr ElementFactory -> ElementFactory)
-> Ptr ElementFactory -> IO ElementFactory
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ElementFactory -> ElementFactory
ElementFactory) Ptr ElementFactory
result'
        ElementFactory -> IO ElementFactory
forall (m :: * -> *) a. Monad m => a -> m a
return ElementFactory
result''
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
name'
    Maybe ElementFactory -> IO (Maybe ElementFactory)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ElementFactory
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method ElementFactory::list_filter
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TGList
--                 (TInterface Name { namespace = "Gst" , name = "ElementFactory" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GList of\n    #GstElementFactory to filter"
--                 , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstCaps" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "direction"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "PadDirection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstPadDirection to filter on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "subsetonly"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to filter on caps subsets or not."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "Gst" , name = "ElementFactory" }))
-- throws : False
-- Skip return : False

foreign import ccall "gst_element_factory_list_filter" gst_element_factory_list_filter :: 
    Ptr (GList (Ptr ElementFactory)) ->     -- list : TGList (TInterface (Name {namespace = "Gst", name = "ElementFactory"}))
    Ptr Gst.Caps.Caps ->                    -- caps : TInterface (Name {namespace = "Gst", name = "Caps"})
    CUInt ->                                -- direction : TInterface (Name {namespace = "Gst", name = "PadDirection"})
    CInt ->                                 -- subsetonly : TBasicType TBoolean
    IO (Ptr (GList (Ptr ElementFactory)))

-- | Filter out all the elementfactories in /@list@/ that can handle /@caps@/ in
-- the given direction.
-- 
-- If /@subsetonly@/ is 'P.True', then only the elements whose pads templates
-- are a complete superset of /@caps@/ will be returned. Else any element
-- whose pad templates caps can intersect with /@caps@/ will be returned.
elementFactoryListFilter ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    [a]
    -- ^ /@list@/: a t'GI.GLib.Structs.List.List' of
    --     t'GI.Gst.Objects.ElementFactory.ElementFactory' to filter
    -> Gst.Caps.Caps
    -- ^ /@caps@/: a t'GI.Gst.Structs.Caps.Caps'
    -> Gst.Enums.PadDirection
    -- ^ /@direction@/: a t'GI.Gst.Enums.PadDirection' to filter on
    -> Bool
    -- ^ /@subsetonly@/: whether to filter on caps subsets or not.
    -> m [ElementFactory]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of
    --     t'GI.Gst.Objects.ElementFactory.ElementFactory' elements that match the given requisites.
    --     Use @/gst_plugin_feature_list_free/@ after usage.
elementFactoryListFilter :: [a] -> Caps -> PadDirection -> Bool -> m [ElementFactory]
elementFactoryListFilter [a]
list Caps
caps PadDirection
direction Bool
subsetonly = IO [ElementFactory] -> m [ElementFactory]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ElementFactory] -> m [ElementFactory])
-> IO [ElementFactory] -> m [ElementFactory]
forall a b. (a -> b) -> a -> b
$ do
    [Ptr ElementFactory]
list' <- (a -> IO (Ptr ElementFactory)) -> [a] -> IO [Ptr ElementFactory]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [a]
list
    Ptr (GList (Ptr ElementFactory))
list'' <- [Ptr ElementFactory] -> IO (Ptr (GList (Ptr ElementFactory)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr ElementFactory]
list'
    Ptr Caps
caps' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
caps
    let direction' :: CUInt
direction' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PadDirection -> Int) -> PadDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PadDirection -> Int
forall a. Enum a => a -> Int
fromEnum) PadDirection
direction
    let subsetonly' :: CInt
subsetonly' = (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
subsetonly
    Ptr (GList (Ptr ElementFactory))
result <- Ptr (GList (Ptr ElementFactory))
-> Ptr Caps
-> CUInt
-> CInt
-> IO (Ptr (GList (Ptr ElementFactory)))
gst_element_factory_list_filter Ptr (GList (Ptr ElementFactory))
list'' Ptr Caps
caps' CUInt
direction' CInt
subsetonly'
    [Ptr ElementFactory]
result' <- Ptr (GList (Ptr ElementFactory)) -> IO [Ptr ElementFactory]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ElementFactory))
result
    [ElementFactory]
result'' <- (Ptr ElementFactory -> IO ElementFactory)
-> [Ptr ElementFactory] -> IO [ElementFactory]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr ElementFactory -> ElementFactory)
-> Ptr ElementFactory -> IO ElementFactory
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ElementFactory -> ElementFactory
ElementFactory) [Ptr ElementFactory]
result'
    Ptr (GList (Ptr ElementFactory)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr ElementFactory))
result
    (a -> IO ()) -> [a] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [a]
list
    Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Caps
caps
    Ptr (GList (Ptr ElementFactory)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr ElementFactory))
list''
    [ElementFactory] -> IO [ElementFactory]
forall (m :: * -> *) a. Monad m => a -> m a
return [ElementFactory]
result''

#if defined(ENABLE_OVERLOADING)
#endif

-- method ElementFactory::list_get_elements
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "type"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstElementFactoryListType"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "minrank"
--           , argType = TInterface Name { namespace = "Gst" , name = "Rank" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Minimum rank" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "Gst" , name = "ElementFactory" }))
-- throws : False
-- Skip return : False

foreign import ccall "gst_element_factory_list_get_elements" gst_element_factory_list_get_elements :: 
    Word64 ->                               -- type : TBasicType TUInt64
    CUInt ->                                -- minrank : TInterface (Name {namespace = "Gst", name = "Rank"})
    IO (Ptr (GList (Ptr ElementFactory)))

-- | Get a list of factories that match the given /@type@/. Only elements
-- with a rank greater or equal to /@minrank@/ will be returned.
-- The list of factories is returned by decreasing rank.
elementFactoryListGetElements ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word64
    -- ^ /@type@/: a @/GstElementFactoryListType/@
    -> Gst.Enums.Rank
    -- ^ /@minrank@/: Minimum rank
    -> m [ElementFactory]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of
    --     t'GI.Gst.Objects.ElementFactory.ElementFactory' elements. Use 'GI.Gst.Objects.PluginFeature.pluginFeatureListFree' after
    --     usage.
elementFactoryListGetElements :: CGType -> Rank -> m [ElementFactory]
elementFactoryListGetElements CGType
type_ Rank
minrank = IO [ElementFactory] -> m [ElementFactory]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ElementFactory] -> m [ElementFactory])
-> IO [ElementFactory] -> m [ElementFactory]
forall a b. (a -> b) -> a -> b
$ do
    let minrank' :: CUInt
minrank' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Rank -> Int) -> Rank -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rank -> Int
forall a. Enum a => a -> Int
fromEnum) Rank
minrank
    Ptr (GList (Ptr ElementFactory))
result <- CGType -> CUInt -> IO (Ptr (GList (Ptr ElementFactory)))
gst_element_factory_list_get_elements CGType
type_ CUInt
minrank'
    [Ptr ElementFactory]
result' <- Ptr (GList (Ptr ElementFactory)) -> IO [Ptr ElementFactory]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ElementFactory))
result
    [ElementFactory]
result'' <- (Ptr ElementFactory -> IO ElementFactory)
-> [Ptr ElementFactory] -> IO [ElementFactory]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr ElementFactory -> ElementFactory)
-> Ptr ElementFactory -> IO ElementFactory
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ElementFactory -> ElementFactory
ElementFactory) [Ptr ElementFactory]
result'
    Ptr (GList (Ptr ElementFactory)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr ElementFactory))
result
    [ElementFactory] -> IO [ElementFactory]
forall (m :: * -> *) a. Monad m => a -> m a
return [ElementFactory]
result''

#if defined(ENABLE_OVERLOADING)
#endif

-- method ElementFactory::make
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "factoryname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a named factory to instantiate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "name of new element, or %NULL to automatically create\n   a unique name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Element" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_element_factory_make" gst_element_factory_make :: 
    CString ->                              -- factoryname : TBasicType TUTF8
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr Gst.Element.Element)

-- | Create a new element of the type defined by the given element factory.
-- If name is 'P.Nothing', then the element will receive a guaranteed unique name,
-- consisting of the element factory name and a number.
-- If name is given, it will be given the name supplied.
elementFactoryMake ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@factoryname@/: a named factory to instantiate
    -> Maybe (T.Text)
    -- ^ /@name@/: name of new element, or 'P.Nothing' to automatically create
    --    a unique name
    -> m (Maybe Gst.Element.Element)
    -- ^ __Returns:__ new t'GI.Gst.Objects.Element.Element' or 'P.Nothing'
    -- if unable to create element
elementFactoryMake :: Text -> Maybe Text -> m (Maybe Element)
elementFactoryMake Text
factoryname 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 CChar
factoryname' <- Text -> IO (Ptr CChar)
textToCString Text
factoryname
    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 CChar -> Ptr CChar -> IO (Ptr Element)
gst_element_factory_make Ptr CChar
factoryname' 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''
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
factoryname'
    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)
#endif