module GI.Gst.Structs.ParseContext
(
ParseContext(..) ,
noParseContext ,
ParseContextFreeMethodInfo ,
parseContextFree ,
ParseContextGetMissingElementsMethodInfo,
parseContextGetMissingElements ,
parseContextNew ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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
newtype ParseContext = ParseContext (ManagedPtr ParseContext)
foreign import ccall "gst_parse_context_get_type" c_gst_parse_context_get_type ::
IO GType
instance BoxedObject ParseContext where
boxedType _ = c_gst_parse_context_get_type
noParseContext :: Maybe ParseContext
noParseContext = Nothing
instance O.HasAttributeList ParseContext
type instance O.AttributeList ParseContext = ParseContextAttributeList
type ParseContextAttributeList = ('[ ] :: [(Symbol, *)])
foreign import ccall "gst_parse_context_new" gst_parse_context_new ::
IO (Ptr ParseContext)
parseContextNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m ParseContext
parseContextNew = liftIO $ do
result <- gst_parse_context_new
checkUnexpectedReturnNULL "parseContextNew" result
result' <- (wrapBoxed ParseContext) result
return result'
foreign import ccall "gst_parse_context_free" gst_parse_context_free ::
Ptr ParseContext ->
IO ()
parseContextFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
ParseContext
-> m ()
parseContextFree context = liftIO $ do
context' <- B.ManagedPtr.disownBoxed context
gst_parse_context_free context'
touchManagedPtr context
return ()
data ParseContextFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ParseContextFreeMethodInfo ParseContext signature where
overloadedMethod _ = parseContextFree
foreign import ccall "gst_parse_context_get_missing_elements" gst_parse_context_get_missing_elements ::
Ptr ParseContext ->
IO (Ptr CString)
parseContextGetMissingElements ::
(B.CallStack.HasCallStack, MonadIO m) =>
ParseContext
-> m [T.Text]
parseContextGetMissingElements context = liftIO $ do
context' <- unsafeManagedPtrGetPtr context
result <- gst_parse_context_get_missing_elements context'
checkUnexpectedReturnNULL "parseContextGetMissingElements" result
result' <- unpackZeroTerminatedUTF8CArray result
mapZeroTerminatedCArray freeMem result
freeMem result
touchManagedPtr context
return result'
data ParseContextGetMissingElementsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.MethodInfo ParseContextGetMissingElementsMethodInfo ParseContext signature where
overloadedMethod _ = parseContextGetMissingElements
type family ResolveParseContextMethod (t :: Symbol) (o :: *) :: * where
ResolveParseContextMethod "free" o = ParseContextFreeMethodInfo
ResolveParseContextMethod "getMissingElements" o = ParseContextGetMissingElementsMethodInfo
ResolveParseContextMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveParseContextMethod t ParseContext, O.MethodInfo info ParseContext p) => O.IsLabelProxy t (ParseContext -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveParseContextMethod t ParseContext, O.MethodInfo info ParseContext p) => O.IsLabel t (ParseContext -> p) where
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif