{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Objects.ElementFactory
    ( 
    ElementFactory(..)                      ,
    IsElementFactory                        ,
    toElementFactory                        ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveElementFactoryMethod             ,
#endif
#if defined(ENABLE_OVERLOADING)
    ElementFactoryCanSinkAllCapsMethodInfo  ,
#endif
    elementFactoryCanSinkAllCaps            ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryCanSinkAnyCapsMethodInfo  ,
#endif
    elementFactoryCanSinkAnyCaps            ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryCanSrcAllCapsMethodInfo   ,
#endif
    elementFactoryCanSrcAllCaps             ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryCanSrcAnyCapsMethodInfo   ,
#endif
    elementFactoryCanSrcAnyCaps             ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryCreateMethodInfo          ,
#endif
    elementFactoryCreate                    ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryCreateWithPropertiesMethodInfo,
#endif
    elementFactoryCreateWithProperties      ,
    elementFactoryFind                      ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetElementTypeMethodInfo  ,
#endif
    elementFactoryGetElementType            ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetMetadataMethodInfo     ,
#endif
    elementFactoryGetMetadata               ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetMetadataKeysMethodInfo ,
#endif
    elementFactoryGetMetadataKeys           ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetNumPadTemplatesMethodInfo,
#endif
    elementFactoryGetNumPadTemplates        ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetSkipDocumentationMethodInfo,
#endif
    elementFactoryGetSkipDocumentation      ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetStaticPadTemplatesMethodInfo,
#endif
    elementFactoryGetStaticPadTemplates     ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetUriProtocolsMethodInfo ,
#endif
    elementFactoryGetUriProtocols           ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryGetUriTypeMethodInfo      ,
#endif
    elementFactoryGetUriType                ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryHasInterfaceMethodInfo    ,
#endif
    elementFactoryHasInterface              ,
    elementFactoryListFilter                ,
    elementFactoryListGetElements           ,
#if defined(ENABLE_OVERLOADING)
    ElementFactoryListIsTypeMethodInfo      ,
#endif
    elementFactoryListIsType                ,
    elementFactoryMake                      ,
    elementFactoryMakeWithProperties        ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.Date as GLib.Date
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GLib.Unions.Mutex as GLib.Mutex
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.ValueArray as GObject.ValueArray
import qualified GI.Gst.Callbacks as Gst.Callbacks
import {-# SOURCE #-} qualified GI.Gst.Enums as Gst.Enums
import {-# SOURCE #-} qualified GI.Gst.Flags as Gst.Flags
import {-# SOURCE #-} qualified GI.Gst.Objects.Allocator as Gst.Allocator
import {-# SOURCE #-} qualified GI.Gst.Objects.BufferPool as Gst.BufferPool
import {-# SOURCE #-} qualified GI.Gst.Objects.Bus as Gst.Bus
import {-# SOURCE #-} qualified GI.Gst.Objects.Clock as Gst.Clock
import {-# SOURCE #-} qualified GI.Gst.Objects.ControlBinding as Gst.ControlBinding
import {-# SOURCE #-} qualified GI.Gst.Objects.Device as Gst.Device
import {-# SOURCE #-} qualified GI.Gst.Objects.Element as Gst.Element
import {-# SOURCE #-} qualified GI.Gst.Objects.Object as Gst.Object
import {-# SOURCE #-} qualified GI.Gst.Objects.Pad as Gst.Pad
import {-# SOURCE #-} qualified GI.Gst.Objects.PadTemplate as Gst.PadTemplate
import {-# SOURCE #-} qualified GI.Gst.Objects.Plugin as Gst.Plugin
import {-# SOURCE #-} qualified GI.Gst.Objects.PluginFeature as Gst.PluginFeature
import {-# SOURCE #-} qualified GI.Gst.Objects.Stream as Gst.Stream
import {-# SOURCE #-} qualified GI.Gst.Objects.StreamCollection as Gst.StreamCollection
import {-# SOURCE #-} qualified GI.Gst.Structs.AllocationParams as Gst.AllocationParams
import {-# SOURCE #-} qualified GI.Gst.Structs.Buffer as Gst.Buffer
import {-# SOURCE #-} qualified GI.Gst.Structs.BufferList as Gst.BufferList
import {-# SOURCE #-} qualified GI.Gst.Structs.BufferPoolAcquireParams as Gst.BufferPoolAcquireParams
import {-# SOURCE #-} qualified GI.Gst.Structs.ByteArrayInterface as Gst.ByteArrayInterface
import {-# SOURCE #-} qualified GI.Gst.Structs.Caps as Gst.Caps
import {-# SOURCE #-} qualified GI.Gst.Structs.CapsFeatures as Gst.CapsFeatures
import {-# SOURCE #-} qualified GI.Gst.Structs.Context as Gst.Context
import {-# SOURCE #-} qualified GI.Gst.Structs.CustomMeta as Gst.CustomMeta
import {-# SOURCE #-} qualified GI.Gst.Structs.DateTime as Gst.DateTime
import {-# SOURCE #-} qualified GI.Gst.Structs.Event as Gst.Event
import {-# SOURCE #-} qualified GI.Gst.Structs.Iterator as Gst.Iterator
import {-# SOURCE #-} qualified GI.Gst.Structs.MapInfo as Gst.MapInfo
import {-# SOURCE #-} qualified GI.Gst.Structs.Memory as Gst.Memory
import {-# SOURCE #-} qualified GI.Gst.Structs.Message as Gst.Message
import {-# SOURCE #-} qualified GI.Gst.Structs.Meta as Gst.Meta
import {-# SOURCE #-} qualified GI.Gst.Structs.MetaInfo as Gst.MetaInfo
import {-# SOURCE #-} qualified GI.Gst.Structs.MiniObject as Gst.MiniObject
import {-# SOURCE #-} qualified GI.Gst.Structs.ParentBufferMeta as Gst.ParentBufferMeta
import {-# SOURCE #-} qualified GI.Gst.Structs.ProtectionMeta as Gst.ProtectionMeta
import {-# SOURCE #-} qualified GI.Gst.Structs.Query as Gst.Query
import {-# SOURCE #-} qualified GI.Gst.Structs.ReferenceTimestampMeta as Gst.ReferenceTimestampMeta
import {-# SOURCE #-} qualified GI.Gst.Structs.Sample as Gst.Sample
import {-# SOURCE #-} qualified GI.Gst.Structs.Segment as Gst.Segment
import {-# SOURCE #-} qualified GI.Gst.Structs.StaticCaps as Gst.StaticCaps
import {-# SOURCE #-} qualified GI.Gst.Structs.StaticPadTemplate as Gst.StaticPadTemplate
import {-# SOURCE #-} qualified GI.Gst.Structs.Structure as Gst.Structure
import {-# SOURCE #-} qualified GI.Gst.Structs.TagList as Gst.TagList
import {-# SOURCE #-} qualified GI.Gst.Structs.Toc as Gst.Toc
import {-# SOURCE #-} qualified GI.Gst.Structs.TocEntry as Gst.TocEntry
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gst.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
#endif
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
$c== :: ElementFactory -> ElementFactory -> Bool
== :: ElementFactory -> ElementFactory -> Bool
$c/= :: ElementFactory -> ElementFactory -> Bool
/= :: 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
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]
toElementFactory :: (MIO.MonadIO m, IsElementFactory o) => o -> m ElementFactory
toElementFactory :: forall (m :: * -> *) o.
(MonadIO m, IsElementFactory o) =>
o -> m ElementFactory
toElementFactory = IO ElementFactory -> m ElementFactory
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr ElementFactory -> ElementFactory
ElementFactory
instance B.GValue.IsGValue (Maybe ElementFactory) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gst_element_factory_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ElementFactory -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ElementFactory
P.Nothing = Ptr GValue -> Ptr ElementFactory -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ElementFactory
forall a. Ptr a
FP.nullPtr :: FP.Ptr ElementFactory)
    gvalueSet_ Ptr GValue
gv (P.Just ElementFactory
obj) = ElementFactory -> (Ptr ElementFactory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ElementFactory
obj (Ptr GValue -> Ptr ElementFactory -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ElementFactory)
gvalueGet_ Ptr GValue
gv = do
        Ptr ElementFactory
ptr <- Ptr GValue -> IO (Ptr ElementFactory)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ElementFactory)
        if Ptr ElementFactory
ptr Ptr ElementFactory -> Ptr ElementFactory -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ElementFactory
forall a. Ptr a
FP.nullPtr
        then ElementFactory -> Maybe ElementFactory
forall a. a -> Maybe a
P.Just (ElementFactory -> Maybe ElementFactory)
-> IO ElementFactory -> IO (Maybe ElementFactory)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe ElementFactory -> IO (Maybe ElementFactory)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ElementFactory
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveElementFactoryMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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 "createWithProperties" o = ElementFactoryCreateWithPropertiesMethodInfo
    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 "getSkipDocumentation" o = ElementFactoryGetSkipDocumentationMethodInfo
    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.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveElementFactoryMethod t ElementFactory, O.OverloadedMethod info ElementFactory p, R.HasField t ElementFactory p) => R.HasField t ElementFactory p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveElementFactoryMethod t ElementFactory, O.OverloadedMethodInfo info ElementFactory) => OL.IsLabel t (O.MethodProxy info ElementFactory) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#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, DK.Type)])
#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, DK.Type)])
#endif
foreign import ccall "gst_element_factory_can_sink_all_caps" gst_element_factory_can_sink_all_caps :: 
    Ptr ElementFactory ->                   
    Ptr Gst.Caps.Caps ->                    
    IO CInt
elementFactoryCanSinkAllCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> Gst.Caps.Caps
    
    -> m Bool
    
elementFactoryCanSinkAllCaps :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> Caps -> m Bool
elementFactoryCanSinkAllCaps a
factory Caps
caps = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 a. a -> IO a
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.OverloadedMethod ElementFactoryCanSinkAllCapsMethodInfo a signature where
    overloadedMethod = elementFactoryCanSinkAllCaps
instance O.OverloadedMethodInfo ElementFactoryCanSinkAllCapsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryCanSinkAllCaps",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryCanSinkAllCaps"
        })
#endif
foreign import ccall "gst_element_factory_can_sink_any_caps" gst_element_factory_can_sink_any_caps :: 
    Ptr ElementFactory ->                   
    Ptr Gst.Caps.Caps ->                    
    IO CInt
elementFactoryCanSinkAnyCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> Gst.Caps.Caps
    
    -> m Bool
    
elementFactoryCanSinkAnyCaps :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> Caps -> m Bool
elementFactoryCanSinkAnyCaps a
factory Caps
caps = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 a. a -> IO a
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.OverloadedMethod ElementFactoryCanSinkAnyCapsMethodInfo a signature where
    overloadedMethod = elementFactoryCanSinkAnyCaps
instance O.OverloadedMethodInfo ElementFactoryCanSinkAnyCapsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryCanSinkAnyCaps",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryCanSinkAnyCaps"
        })
#endif
foreign import ccall "gst_element_factory_can_src_all_caps" gst_element_factory_can_src_all_caps :: 
    Ptr ElementFactory ->                   
    Ptr Gst.Caps.Caps ->                    
    IO CInt
elementFactoryCanSrcAllCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> Gst.Caps.Caps
    
    -> m Bool
    
elementFactoryCanSrcAllCaps :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> Caps -> m Bool
elementFactoryCanSrcAllCaps a
factory Caps
caps = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 a. a -> IO a
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.OverloadedMethod ElementFactoryCanSrcAllCapsMethodInfo a signature where
    overloadedMethod = elementFactoryCanSrcAllCaps
instance O.OverloadedMethodInfo ElementFactoryCanSrcAllCapsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryCanSrcAllCaps",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryCanSrcAllCaps"
        })
#endif
foreign import ccall "gst_element_factory_can_src_any_caps" gst_element_factory_can_src_any_caps :: 
    Ptr ElementFactory ->                   
    Ptr Gst.Caps.Caps ->                    
    IO CInt
elementFactoryCanSrcAnyCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> Gst.Caps.Caps
    
    -> m Bool
    
elementFactoryCanSrcAnyCaps :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> Caps -> m Bool
elementFactoryCanSrcAnyCaps a
factory Caps
caps = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 a. a -> IO a
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.OverloadedMethod ElementFactoryCanSrcAnyCapsMethodInfo a signature where
    overloadedMethod = elementFactoryCanSrcAnyCaps
instance O.OverloadedMethodInfo ElementFactoryCanSrcAnyCapsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryCanSrcAnyCaps",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryCanSrcAnyCaps"
        })
#endif
foreign import ccall "gst_element_factory_create" gst_element_factory_create :: 
    Ptr ElementFactory ->                   
    CString ->                              
    IO (Ptr Gst.Element.Element)
elementFactoryCreate ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> Maybe (T.Text)
    
    
    -> m (Maybe Gst.Element.Element)
    
    
elementFactoryCreate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> Maybe Text -> m (Maybe Element)
elementFactoryCreate a
factory Maybe Text
name = IO (Maybe Element) -> m (Maybe Element)
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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.OverloadedMethod ElementFactoryCreateMethodInfo a signature where
    overloadedMethod = elementFactoryCreate
instance O.OverloadedMethodInfo ElementFactoryCreateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryCreate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryCreate"
        })
#endif
foreign import ccall "gst_element_factory_create_with_properties" gst_element_factory_create_with_properties :: 
    Ptr ElementFactory ->                   
    Word32 ->                               
    Ptr CString ->                          
    Ptr B.GValue.GValue ->                  
    IO (Ptr Gst.Element.Element)
elementFactoryCreateWithProperties ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> Maybe ([T.Text])
    
    -> Maybe ([GValue])
    
    -> m (Maybe Gst.Element.Element)
    
    
elementFactoryCreateWithProperties :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> Maybe [Text] -> Maybe [GValue] -> m (Maybe Element)
elementFactoryCreateWithProperties a
factory Maybe [Text]
names Maybe [GValue]
values = IO (Maybe Element) -> m (Maybe Element)
forall a. IO a -> m a
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
    let n :: Word32
n = case Maybe [GValue]
values of
            Maybe [GValue]
Nothing -> Word32
0
            Just [GValue]
jValues -> Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [GValue] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [GValue]
jValues
    let names_expected_length_ :: Word32
names_expected_length_ = case Maybe [Text]
names of
            Maybe [Text]
Nothing -> Word32
0
            Just [Text]
jNames -> Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Text] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Text]
jNames
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Word32
names_expected_length_ Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word32
n) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        [Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"Gst.elementFactoryCreateWithProperties : length of 'names' does not agree with that of 'values'."
    Ptr ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr (Ptr CChar)
maybeNames <- case Maybe [Text]
names of
        Maybe [Text]
Nothing -> Ptr (Ptr CChar) -> IO (Ptr (Ptr CChar))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr CChar)
forall a. Ptr a
nullPtr
        Just [Text]
jNames -> do
            Ptr (Ptr CChar)
jNames' <- [Text] -> IO (Ptr (Ptr CChar))
packUTF8CArray [Text]
jNames
            Ptr (Ptr CChar) -> IO (Ptr (Ptr CChar))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr CChar)
jNames'
    Ptr GValue
maybeValues <- case Maybe [GValue]
values of
        Maybe [GValue]
Nothing -> Ptr GValue -> IO (Ptr GValue)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GValue
forall a. Ptr a
nullPtr
        Just [GValue]
jValues -> do
            Ptr GValue
jValues' <- [GValue] -> IO (Ptr GValue)
B.GValue.packGValueArray [GValue]
jValues
            Ptr GValue -> IO (Ptr GValue)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GValue
jValues'
    Ptr Element
result <- Ptr ElementFactory
-> Word32 -> Ptr (Ptr CChar) -> Ptr GValue -> IO (Ptr Element)
gst_element_factory_create_with_properties Ptr ElementFactory
factory' Word32
n Ptr (Ptr CChar)
maybeNames Ptr GValue
maybeValues
    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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Element
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    Maybe [GValue] -> ([GValue] -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe [GValue]
values ((GValue -> IO ()) -> [GValue] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr)
    (Word32 -> (Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Word32
n) Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
maybeNames
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
maybeNames
    Ptr GValue -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr GValue
maybeValues
    Maybe Element -> IO (Maybe Element)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Element
maybeResult
#if defined(ENABLE_OVERLOADING)
data ElementFactoryCreateWithPropertiesMethodInfo
instance (signature ~ (Maybe ([T.Text]) -> Maybe ([GValue]) -> m (Maybe Gst.Element.Element)), MonadIO m, IsElementFactory a) => O.OverloadedMethod ElementFactoryCreateWithPropertiesMethodInfo a signature where
    overloadedMethod = elementFactoryCreateWithProperties
instance O.OverloadedMethodInfo ElementFactoryCreateWithPropertiesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryCreateWithProperties",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryCreateWithProperties"
        })
#endif
foreign import ccall "gst_element_factory_get_element_type" gst_element_factory_get_element_type :: 
    Ptr ElementFactory ->                   
    IO CGType
elementFactoryGetElementType ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> m GType
    
    
elementFactoryGetElementType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> m GType
elementFactoryGetElementType a
factory = IO GType -> m GType
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod ElementFactoryGetElementTypeMethodInfo a signature where
    overloadedMethod = elementFactoryGetElementType
instance O.OverloadedMethodInfo ElementFactoryGetElementTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryGetElementType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryGetElementType"
        })
#endif
foreign import ccall "gst_element_factory_get_metadata" gst_element_factory_get_metadata :: 
    Ptr ElementFactory ->                   
    CString ->                              
    IO CString
elementFactoryGetMetadata ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> T.Text
    
    -> m (Maybe T.Text)
    
    
elementFactoryGetMetadata :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> Text -> m (Maybe Text)
elementFactoryGetMetadata a
factory Text
key = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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.OverloadedMethod ElementFactoryGetMetadataMethodInfo a signature where
    overloadedMethod = elementFactoryGetMetadata
instance O.OverloadedMethodInfo ElementFactoryGetMetadataMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryGetMetadata",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryGetMetadata"
        })
#endif
foreign import ccall "gst_element_factory_get_metadata_keys" gst_element_factory_get_metadata_keys :: 
    Ptr ElementFactory ->                   
    IO (Ptr CString)
elementFactoryGetMetadataKeys ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> m (Maybe [T.Text])
    
    
    
elementFactoryGetMetadataKeys :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> m (Maybe [Text])
elementFactoryGetMetadataKeys a
factory = IO (Maybe [Text]) -> m (Maybe [Text])
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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.OverloadedMethod ElementFactoryGetMetadataKeysMethodInfo a signature where
    overloadedMethod = elementFactoryGetMetadataKeys
instance O.OverloadedMethodInfo ElementFactoryGetMetadataKeysMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryGetMetadataKeys",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryGetMetadataKeys"
        })
#endif
foreign import ccall "gst_element_factory_get_num_pad_templates" gst_element_factory_get_num_pad_templates :: 
    Ptr ElementFactory ->                   
    IO Word32
elementFactoryGetNumPadTemplates ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> m Word32
    
elementFactoryGetNumPadTemplates :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> m Word32
elementFactoryGetNumPadTemplates a
factory = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 a. a -> IO a
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.OverloadedMethod ElementFactoryGetNumPadTemplatesMethodInfo a signature where
    overloadedMethod = elementFactoryGetNumPadTemplates
instance O.OverloadedMethodInfo ElementFactoryGetNumPadTemplatesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryGetNumPadTemplates",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryGetNumPadTemplates"
        })
#endif
foreign import ccall "gst_element_factory_get_skip_documentation" gst_element_factory_get_skip_documentation :: 
    Ptr ElementFactory ->                   
    IO CInt
elementFactoryGetSkipDocumentation ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> m Bool
    
elementFactoryGetSkipDocumentation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> m Bool
elementFactoryGetSkipDocumentation a
factory = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ElementFactory
factory' <- a -> IO (Ptr ElementFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    CInt
result <- Ptr ElementFactory -> IO CInt
gst_element_factory_get_skip_documentation Ptr ElementFactory
factory'
    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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ElementFactoryGetSkipDocumentationMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsElementFactory a) => O.OverloadedMethod ElementFactoryGetSkipDocumentationMethodInfo a signature where
    overloadedMethod = elementFactoryGetSkipDocumentation
instance O.OverloadedMethodInfo ElementFactoryGetSkipDocumentationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryGetSkipDocumentation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryGetSkipDocumentation"
        })
#endif
foreign import ccall "gst_element_factory_get_static_pad_templates" gst_element_factory_get_static_pad_templates :: 
    Ptr ElementFactory ->                   
    IO (Ptr (GList (Ptr Gst.StaticPadTemplate.StaticPadTemplate)))
elementFactoryGetStaticPadTemplates ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> m [Gst.StaticPadTemplate.StaticPadTemplate]
    
    
elementFactoryGetStaticPadTemplates :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> m [StaticPadTemplate]
elementFactoryGetStaticPadTemplates a
factory = IO [StaticPadTemplate] -> m [StaticPadTemplate]
forall a. IO a -> m a
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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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 a. a -> IO a
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.OverloadedMethod ElementFactoryGetStaticPadTemplatesMethodInfo a signature where
    overloadedMethod = elementFactoryGetStaticPadTemplates
instance O.OverloadedMethodInfo ElementFactoryGetStaticPadTemplatesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryGetStaticPadTemplates",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryGetStaticPadTemplates"
        })
#endif
foreign import ccall "gst_element_factory_get_uri_protocols" gst_element_factory_get_uri_protocols :: 
    Ptr ElementFactory ->                   
    IO (Ptr CString)
elementFactoryGetUriProtocols ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> m [T.Text]
    
    
elementFactoryGetUriProtocols :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> m [Text]
elementFactoryGetUriProtocols a
factory = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 a. a -> IO a
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.OverloadedMethod ElementFactoryGetUriProtocolsMethodInfo a signature where
    overloadedMethod = elementFactoryGetUriProtocols
instance O.OverloadedMethodInfo ElementFactoryGetUriProtocolsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryGetUriProtocols",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryGetUriProtocols"
        })
#endif
foreign import ccall "gst_element_factory_get_uri_type" gst_element_factory_get_uri_type :: 
    Ptr ElementFactory ->                   
    IO CUInt
elementFactoryGetUriType ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> m Gst.Enums.URIType
    
elementFactoryGetUriType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> m URIType
elementFactoryGetUriType a
factory = IO URIType -> m URIType
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod ElementFactoryGetUriTypeMethodInfo a signature where
    overloadedMethod = elementFactoryGetUriType
instance O.OverloadedMethodInfo ElementFactoryGetUriTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryGetUriType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryGetUriType"
        })
#endif
foreign import ccall "gst_element_factory_has_interface" gst_element_factory_has_interface :: 
    Ptr ElementFactory ->                   
    CString ->                              
    IO CInt
elementFactoryHasInterface ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> T.Text
    
    -> m Bool
    
elementFactoryHasInterface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> Text -> m Bool
elementFactoryHasInterface a
factory Text
interfacename = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 a. a -> IO a
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.OverloadedMethod ElementFactoryHasInterfaceMethodInfo a signature where
    overloadedMethod = elementFactoryHasInterface
instance O.OverloadedMethodInfo ElementFactoryHasInterfaceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryHasInterface",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryHasInterface"
        })
#endif
foreign import ccall "gst_element_factory_list_is_type" gst_element_factory_list_is_type :: 
    Ptr ElementFactory ->                   
    Word64 ->                               
    IO CInt
elementFactoryListIsType ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    a
    
    -> Word64
    
    -> m Bool
    
elementFactoryListIsType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
a -> CGType -> m Bool
elementFactoryListIsType a
factory CGType
type_ = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 a. a -> IO a
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.OverloadedMethod ElementFactoryListIsTypeMethodInfo a signature where
    overloadedMethod = elementFactoryListIsType
instance O.OverloadedMethodInfo ElementFactoryListIsTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Objects.ElementFactory.elementFactoryListIsType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Objects-ElementFactory.html#v:elementFactoryListIsType"
        })
#endif
foreign import ccall "gst_element_factory_find" gst_element_factory_find :: 
    CString ->                              
    IO (Ptr ElementFactory)
elementFactoryFind ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    -> m (Maybe ElementFactory)
    
    
elementFactoryFind :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe ElementFactory)
elementFactoryFind Text
name = IO (Maybe ElementFactory) -> m (Maybe ElementFactory)
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ElementFactory
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gst_element_factory_list_filter" gst_element_factory_list_filter :: 
    Ptr (GList (Ptr ElementFactory)) ->     
    Ptr Gst.Caps.Caps ->                    
    CUInt ->                                
    CInt ->                                 
    IO (Ptr (GList (Ptr ElementFactory)))
elementFactoryListFilter ::
    (B.CallStack.HasCallStack, MonadIO m, IsElementFactory a) =>
    [a]
    
    
    -> Gst.Caps.Caps
    
    -> Gst.Enums.PadDirection
    
    -> Bool
    
    -> m [ElementFactory]
    
    
    
elementFactoryListFilter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsElementFactory a) =>
[a] -> Caps -> PadDirection -> Bool -> m [ElementFactory]
elementFactoryListFilter [a]
list Caps
caps PadDirection
direction Bool
subsetonly = IO [ElementFactory] -> m [ElementFactory]
forall a. IO a -> m a
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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ElementFactory]
result''
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gst_element_factory_list_get_elements" gst_element_factory_list_get_elements :: 
    Word64 ->                               
    CUInt ->                                
    IO (Ptr (GList (Ptr ElementFactory)))
elementFactoryListGetElements ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word64
    
    -> Gst.Enums.Rank
    
    -> m [ElementFactory]
    
    
    
elementFactoryListGetElements :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CGType -> Rank -> m [ElementFactory]
elementFactoryListGetElements CGType
type_ Rank
minrank = IO [ElementFactory] -> m [ElementFactory]
forall a. IO a -> m a
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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ElementFactory]
result''
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gst_element_factory_make" gst_element_factory_make :: 
    CString ->                              
    CString ->                              
    IO (Ptr Gst.Element.Element)
elementFactoryMake ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    -> Maybe (T.Text)
    
    
    -> m (Maybe Gst.Element.Element)
    
    
elementFactoryMake :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Maybe Text -> m (Maybe Element)
elementFactoryMake Text
factoryname Maybe Text
name = IO (Maybe Element) -> m (Maybe Element)
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Element
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gst_element_factory_make_with_properties" gst_element_factory_make_with_properties :: 
    CString ->                              
    Word32 ->                               
    Ptr CString ->                          
    Ptr B.GValue.GValue ->                  
    IO (Ptr Gst.Element.Element)
elementFactoryMakeWithProperties ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    -> Maybe ([T.Text])
    
    -> Maybe ([GValue])
    
    -> m (Maybe Gst.Element.Element)
    
    
elementFactoryMakeWithProperties :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Maybe [Text] -> Maybe [GValue] -> m (Maybe Element)
elementFactoryMakeWithProperties Text
factoryname Maybe [Text]
names Maybe [GValue]
values = IO (Maybe Element) -> m (Maybe Element)
forall a. IO a -> m a
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
    let n :: Word32
n = case Maybe [GValue]
values of
            Maybe [GValue]
Nothing -> Word32
0
            Just [GValue]
jValues -> Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [GValue] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [GValue]
jValues
    let names_expected_length_ :: Word32
names_expected_length_ = case Maybe [Text]
names of
            Maybe [Text]
Nothing -> Word32
0
            Just [Text]
jNames -> Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Text] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Text]
jNames
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Word32
names_expected_length_ Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word32
n) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        [Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"Gst.elementFactoryMakeWithProperties : length of 'names' does not agree with that of 'values'."
    Ptr CChar
factoryname' <- Text -> IO (Ptr CChar)
textToCString Text
factoryname
    Ptr (Ptr CChar)
maybeNames <- case Maybe [Text]
names of
        Maybe [Text]
Nothing -> Ptr (Ptr CChar) -> IO (Ptr (Ptr CChar))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr CChar)
forall a. Ptr a
nullPtr
        Just [Text]
jNames -> do
            Ptr (Ptr CChar)
jNames' <- [Text] -> IO (Ptr (Ptr CChar))
packUTF8CArray [Text]
jNames
            Ptr (Ptr CChar) -> IO (Ptr (Ptr CChar))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr CChar)
jNames'
    Ptr GValue
maybeValues <- case Maybe [GValue]
values of
        Maybe [GValue]
Nothing -> Ptr GValue -> IO (Ptr GValue)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GValue
forall a. Ptr a
nullPtr
        Just [GValue]
jValues -> do
            Ptr GValue
jValues' <- [GValue] -> IO (Ptr GValue)
B.GValue.packGValueArray [GValue]
jValues
            Ptr GValue -> IO (Ptr GValue)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GValue
jValues'
    Ptr Element
result <- Ptr CChar
-> Word32 -> Ptr (Ptr CChar) -> Ptr GValue -> IO (Ptr Element)
gst_element_factory_make_with_properties Ptr CChar
factoryname' Word32
n Ptr (Ptr CChar)
maybeNames Ptr GValue
maybeValues
    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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Element
result''
    Maybe [GValue] -> ([GValue] -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe [GValue]
values ((GValue -> IO ()) -> [GValue] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr)
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
factoryname'
    (Word32 -> (Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Word32
n) Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
maybeNames
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
maybeNames
    Ptr GValue -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr GValue
maybeValues
    Maybe Element -> IO (Maybe Element)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Element
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif