{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Structs.ParseContext
(
ParseContext(..) ,
noParseContext ,
#if defined(ENABLE_OVERLOADING)
ResolveParseContextMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ParseContextCopyMethodInfo ,
#endif
parseContextCopy ,
#if defined(ENABLE_OVERLOADING)
ParseContextFreeMethodInfo ,
#endif
parseContextFree ,
#if defined(ENABLE_OVERLOADING)
ParseContextGetMissingElementsMethodInfo,
#endif
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.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 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
newtype ParseContext = ParseContext (ManagedPtr ParseContext)
deriving (ParseContext -> ParseContext -> Bool
(ParseContext -> ParseContext -> Bool)
-> (ParseContext -> ParseContext -> Bool) -> Eq ParseContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseContext -> ParseContext -> Bool
$c/= :: ParseContext -> ParseContext -> Bool
== :: ParseContext -> ParseContext -> Bool
$c== :: ParseContext -> ParseContext -> Bool
Eq)
foreign import ccall "gst_parse_context_get_type" c_gst_parse_context_get_type ::
IO GType
instance BoxedObject ParseContext where
boxedType :: ParseContext -> IO GType
boxedType _ = IO GType
c_gst_parse_context_get_type
instance B.GValue.IsGValue ParseContext where
toGValue :: ParseContext -> IO GValue
toGValue o :: ParseContext
o = do
GType
gtype <- IO GType
c_gst_parse_context_get_type
ParseContext -> (Ptr ParseContext -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ParseContext
o (GType
-> (GValue -> Ptr ParseContext -> IO ())
-> Ptr ParseContext
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ParseContext -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO ParseContext
fromGValue gv :: GValue
gv = do
Ptr ParseContext
ptr <- GValue -> IO (Ptr ParseContext)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr ParseContext)
(ManagedPtr ParseContext -> ParseContext)
-> Ptr ParseContext -> IO ParseContext
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr ParseContext -> ParseContext
ParseContext Ptr ParseContext
ptr
noParseContext :: Maybe ParseContext
noParseContext :: Maybe ParseContext
noParseContext = Maybe ParseContext
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ParseContext
type instance O.AttributeList ParseContext = ParseContextAttributeList
type ParseContextAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "gst_parse_context_new" gst_parse_context_new ::
IO (Ptr ParseContext)
parseContextNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m (Maybe ParseContext)
parseContextNew :: m (Maybe ParseContext)
parseContextNew = IO (Maybe ParseContext) -> m (Maybe ParseContext)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ParseContext) -> m (Maybe ParseContext))
-> IO (Maybe ParseContext) -> m (Maybe ParseContext)
forall a b. (a -> b) -> a -> b
$ do
Ptr ParseContext
result <- IO (Ptr ParseContext)
gst_parse_context_new
Maybe ParseContext
maybeResult <- Ptr ParseContext
-> (Ptr ParseContext -> IO ParseContext) -> IO (Maybe ParseContext)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ParseContext
result ((Ptr ParseContext -> IO ParseContext) -> IO (Maybe ParseContext))
-> (Ptr ParseContext -> IO ParseContext) -> IO (Maybe ParseContext)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr ParseContext
result' -> do
ParseContext
result'' <- ((ManagedPtr ParseContext -> ParseContext)
-> Ptr ParseContext -> IO ParseContext
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr ParseContext -> ParseContext
ParseContext) Ptr ParseContext
result'
ParseContext -> IO ParseContext
forall (m :: * -> *) a. Monad m => a -> m a
return ParseContext
result''
Maybe ParseContext -> IO (Maybe ParseContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ParseContext
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gst_parse_context_copy" gst_parse_context_copy ::
Ptr ParseContext ->
IO (Ptr ParseContext)
parseContextCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
ParseContext
-> m (Maybe ParseContext)
parseContextCopy :: ParseContext -> m (Maybe ParseContext)
parseContextCopy context :: ParseContext
context = IO (Maybe ParseContext) -> m (Maybe ParseContext)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ParseContext) -> m (Maybe ParseContext))
-> IO (Maybe ParseContext) -> m (Maybe ParseContext)
forall a b. (a -> b) -> a -> b
$ do
Ptr ParseContext
context' <- ParseContext -> IO (Ptr ParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ParseContext
context
Ptr ParseContext
result <- Ptr ParseContext -> IO (Ptr ParseContext)
gst_parse_context_copy Ptr ParseContext
context'
Maybe ParseContext
maybeResult <- Ptr ParseContext
-> (Ptr ParseContext -> IO ParseContext) -> IO (Maybe ParseContext)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ParseContext
result ((Ptr ParseContext -> IO ParseContext) -> IO (Maybe ParseContext))
-> (Ptr ParseContext -> IO ParseContext) -> IO (Maybe ParseContext)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr ParseContext
result' -> do
ParseContext
result'' <- ((ManagedPtr ParseContext -> ParseContext)
-> Ptr ParseContext -> IO ParseContext
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr ParseContext -> ParseContext
ParseContext) Ptr ParseContext
result'
ParseContext -> IO ParseContext
forall (m :: * -> *) a. Monad m => a -> m a
return ParseContext
result''
ParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParseContext
context
Maybe ParseContext -> IO (Maybe ParseContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ParseContext
maybeResult
#if defined(ENABLE_OVERLOADING)
data ParseContextCopyMethodInfo
instance (signature ~ (m (Maybe ParseContext)), MonadIO m) => O.MethodInfo ParseContextCopyMethodInfo ParseContext signature where
overloadedMethod = parseContextCopy
#endif
foreign import ccall "gst_parse_context_free" gst_parse_context_free ::
Ptr ParseContext ->
IO ()
parseContextFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
ParseContext
-> m ()
parseContextFree :: ParseContext -> m ()
parseContextFree context :: ParseContext
context = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr ParseContext
context' <- ParseContext -> IO (Ptr ParseContext)
forall a. (HasCallStack, BoxedObject a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed ParseContext
context
Ptr ParseContext -> IO ()
gst_parse_context_free Ptr ParseContext
context'
ParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParseContext
context
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ParseContextFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ParseContextFreeMethodInfo ParseContext signature where
overloadedMethod = parseContextFree
#endif
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 (Maybe [T.Text])
parseContextGetMissingElements :: ParseContext -> m (Maybe [Text])
parseContextGetMissingElements context :: ParseContext
context = 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 ParseContext
context' <- ParseContext -> IO (Ptr ParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ParseContext
context
Ptr CString
result <- Ptr ParseContext -> IO (Ptr CString)
gst_parse_context_get_missing_elements Ptr ParseContext
context'
Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr CString
result' -> do
[Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
[Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
ParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParseContext
context
Maybe [Text] -> IO (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult
#if defined(ENABLE_OVERLOADING)
data ParseContextGetMissingElementsMethodInfo
instance (signature ~ (m (Maybe [T.Text])), MonadIO m) => O.MethodInfo ParseContextGetMissingElementsMethodInfo ParseContext signature where
overloadedMethod = parseContextGetMissingElements
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveParseContextMethod (t :: Symbol) (o :: *) :: * where
ResolveParseContextMethod "copy" o = ParseContextCopyMethodInfo
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) => OL.IsLabel t (ParseContext -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif