{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A parse context is used to parse a stream of bytes that
-- you expect to contain marked-up text.
-- 
-- See 'GI.GLib.Structs.MarkupParseContext.markupParseContextNew', t'GI.GLib.Structs.MarkupParser.MarkupParser', and so
-- on for more details.

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

module GI.GLib.Structs.MarkupParseContext
    ( 

-- * Exported types
    MarkupParseContext(..)                  ,
    noMarkupParseContext                    ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveMarkupParseContextMethod         ,
#endif


-- ** endParse #method:endParse#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextEndParseMethodInfo    ,
#endif
    markupParseContextEndParse              ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextFreeMethodInfo        ,
#endif
    markupParseContextFree                  ,


-- ** getElement #method:getElement#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextGetElementMethodInfo  ,
#endif
    markupParseContextGetElement            ,


-- ** getUserData #method:getUserData#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextGetUserDataMethodInfo ,
#endif
    markupParseContextGetUserData           ,


-- ** new #method:new#

    markupParseContextNew                   ,


-- ** parse #method:parse#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextParseMethodInfo       ,
#endif
    markupParseContextParse                 ,


-- ** pop #method:pop#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextPopMethodInfo         ,
#endif
    markupParseContextPop                   ,


-- ** push #method:push#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextPushMethodInfo        ,
#endif
    markupParseContextPush                  ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextRefMethodInfo         ,
#endif
    markupParseContextRef                   ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    MarkupParseContextUnrefMethodInfo       ,
#endif
    markupParseContextUnref                 ,




    ) 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

import qualified GI.GLib.Callbacks as GLib.Callbacks
import {-# SOURCE #-} qualified GI.GLib.Flags as GLib.Flags
import {-# SOURCE #-} qualified GI.GLib.Structs.MarkupParser as GLib.MarkupParser

-- | Memory-managed wrapper type.
newtype MarkupParseContext = MarkupParseContext (ManagedPtr MarkupParseContext)
    deriving (MarkupParseContext -> MarkupParseContext -> Bool
(MarkupParseContext -> MarkupParseContext -> Bool)
-> (MarkupParseContext -> MarkupParseContext -> Bool)
-> Eq MarkupParseContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarkupParseContext -> MarkupParseContext -> Bool
$c/= :: MarkupParseContext -> MarkupParseContext -> Bool
== :: MarkupParseContext -> MarkupParseContext -> Bool
$c== :: MarkupParseContext -> MarkupParseContext -> Bool
Eq)
foreign import ccall "g_markup_parse_context_get_type" c_g_markup_parse_context_get_type :: 
    IO GType

instance BoxedObject MarkupParseContext where
    boxedType :: MarkupParseContext -> IO GType
boxedType _ = IO GType
c_g_markup_parse_context_get_type

-- | Convert 'MarkupParseContext' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue MarkupParseContext where
    toGValue :: MarkupParseContext -> IO GValue
toGValue o :: MarkupParseContext
o = do
        GType
gtype <- IO GType
c_g_markup_parse_context_get_type
        MarkupParseContext
-> (Ptr MarkupParseContext -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr MarkupParseContext
o (GType
-> (GValue -> Ptr MarkupParseContext -> IO ())
-> Ptr MarkupParseContext
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr MarkupParseContext -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO MarkupParseContext
fromGValue gv :: GValue
gv = do
        Ptr MarkupParseContext
ptr <- GValue -> IO (Ptr MarkupParseContext)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr MarkupParseContext)
        (ManagedPtr MarkupParseContext -> MarkupParseContext)
-> Ptr MarkupParseContext -> IO MarkupParseContext
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr MarkupParseContext -> MarkupParseContext
MarkupParseContext Ptr MarkupParseContext
ptr
        
    

-- | A convenience alias for `Nothing` :: `Maybe` `MarkupParseContext`.
noMarkupParseContext :: Maybe MarkupParseContext
noMarkupParseContext :: Maybe MarkupParseContext
noMarkupParseContext = Maybe MarkupParseContext
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MarkupParseContext
type instance O.AttributeList MarkupParseContext = MarkupParseContextAttributeList
type MarkupParseContextAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method MarkupParseContext::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "parser"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MarkupParser" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParser" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MarkupParseFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "one or more #GMarkupParseFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to #GMarkupParser functions"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data_dnotify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "user data destroy notifier called when\n    the parse context is freed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GLib" , name = "MarkupParseContext" })
-- throws : False
-- Skip return : False

foreign import ccall "g_markup_parse_context_new" g_markup_parse_context_new :: 
    Ptr GLib.MarkupParser.MarkupParser ->   -- parser : TInterface (Name {namespace = "GLib", name = "MarkupParser"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GLib", name = "MarkupParseFlags"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_data_dnotify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO (Ptr MarkupParseContext)

-- | Creates a new parse context. A parse context is used to parse
-- marked-up documents. You can feed any number of documents into
-- a context, as long as no errors occur; once an error occurs,
-- the parse context can\'t continue to parse text (you have to
-- free it and create a new parse context).
markupParseContextNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.MarkupParser.MarkupParser
    -- ^ /@parser@/: a t'GI.GLib.Structs.MarkupParser.MarkupParser'
    -> [GLib.Flags.MarkupParseFlags]
    -- ^ /@flags@/: one or more t'GI.GLib.Flags.MarkupParseFlags'
    -> Ptr ()
    -- ^ /@userData@/: user data to pass to t'GI.GLib.Structs.MarkupParser.MarkupParser' functions
    -> GLib.Callbacks.DestroyNotify
    -- ^ /@userDataDnotify@/: user data destroy notifier called when
    --     the parse context is freed
    -> m MarkupParseContext
    -- ^ __Returns:__ a new t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
markupParseContextNew :: MarkupParser
-> [MarkupParseFlags]
-> Ptr ()
-> DestroyNotify
-> m MarkupParseContext
markupParseContextNew parser :: MarkupParser
parser flags :: [MarkupParseFlags]
flags userData :: Ptr ()
userData userDataDnotify :: DestroyNotify
userDataDnotify = IO MarkupParseContext -> m MarkupParseContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MarkupParseContext -> m MarkupParseContext)
-> IO MarkupParseContext -> m MarkupParseContext
forall a b. (a -> b) -> a -> b
$ do
    Ptr MarkupParser
parser' <- MarkupParser -> IO (Ptr MarkupParser)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParser
parser
    let flags' :: CUInt
flags' = [MarkupParseFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MarkupParseFlags]
flags
    Ptr (FunPtr DestroyNotify)
ptruserDataDnotify <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
    FunPtr DestroyNotify
userDataDnotify' <- DestroyNotify -> IO (FunPtr DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr DestroyNotify))
-> DestroyNotify -> DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr DestroyNotify) -> Maybe (Ptr (FunPtr DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr DestroyNotify)
ptruserDataDnotify) DestroyNotify
userDataDnotify)
    Ptr (FunPtr DestroyNotify) -> FunPtr DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr DestroyNotify)
ptruserDataDnotify FunPtr DestroyNotify
userDataDnotify'
    Ptr MarkupParseContext
result <- Ptr MarkupParser
-> CUInt
-> Ptr ()
-> FunPtr DestroyNotify
-> IO (Ptr MarkupParseContext)
g_markup_parse_context_new Ptr MarkupParser
parser' CUInt
flags' Ptr ()
userData FunPtr DestroyNotify
userDataDnotify'
    Text -> Ptr MarkupParseContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "markupParseContextNew" Ptr MarkupParseContext
result
    MarkupParseContext
result' <- ((ManagedPtr MarkupParseContext -> MarkupParseContext)
-> Ptr MarkupParseContext -> IO MarkupParseContext
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr MarkupParseContext -> MarkupParseContext
MarkupParseContext) Ptr MarkupParseContext
result
    MarkupParser -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParser
parser
    MarkupParseContext -> IO MarkupParseContext
forall (m :: * -> *) a. Monad m => a -> m a
return MarkupParseContext
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MarkupParseContext::end_parse
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "MarkupParseContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParseContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_markup_parse_context_end_parse" g_markup_parse_context_end_parse :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Signals to the t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext' that all data has been
-- fed into the parse context with 'GI.GLib.Structs.MarkupParseContext.markupParseContextParse'.
-- 
-- This function reports an error if the document isn\'t complete,
-- for example if elements are still open.
markupParseContextEndParse ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
markupParseContextEndParse :: MarkupParseContext -> m ()
markupParseContextEndParse context :: MarkupParseContext
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 MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr MarkupParseContext -> Ptr (Ptr GError) -> IO CInt
g_markup_parse_context_end_parse Ptr MarkupParseContext
context'
        MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextEndParseMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo MarkupParseContextEndParseMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextEndParse

#endif

-- method MarkupParseContext::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "MarkupParseContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParseContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_markup_parse_context_free" g_markup_parse_context_free :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    IO ()

-- | Frees a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'.
-- 
-- This function can\'t be called from inside one of the
-- t'GI.GLib.Structs.MarkupParser.MarkupParser' functions or while a subparser is pushed.
markupParseContextFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> m ()
markupParseContextFree :: MarkupParseContext -> m ()
markupParseContextFree context :: MarkupParseContext
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 MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    Ptr MarkupParseContext -> IO ()
g_markup_parse_context_free Ptr MarkupParseContext
context'
    MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo MarkupParseContextFreeMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextFree

#endif

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

foreign import ccall "g_markup_parse_context_get_element" g_markup_parse_context_get_element :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    IO CString

-- | Retrieves the name of the currently open element.
-- 
-- If called from the start_element or end_element handlers this will
-- give the element_name as passed to those functions. For the parent
-- elements, see @/g_markup_parse_context_get_element_stack()/@.
-- 
-- /Since: 2.2/
markupParseContextGetElement ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> m T.Text
    -- ^ __Returns:__ the name of the currently open element, or 'P.Nothing'
markupParseContextGetElement :: MarkupParseContext -> m Text
markupParseContextGetElement context :: MarkupParseContext
context = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    CString
result <- Ptr MarkupParseContext -> IO CString
g_markup_parse_context_get_element Ptr MarkupParseContext
context'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "markupParseContextGetElement" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextGetElementMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo MarkupParseContextGetElementMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextGetElement

#endif

-- method MarkupParseContext::get_user_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "MarkupParseContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParseContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_markup_parse_context_get_user_data" g_markup_parse_context_get_user_data :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    IO (Ptr ())

-- | Returns the user_data associated with /@context@/.
-- 
-- This will either be the user_data that was provided to
-- 'GI.GLib.Structs.MarkupParseContext.markupParseContextNew' or to the most recent call
-- of 'GI.GLib.Structs.MarkupParseContext.markupParseContextPush'.
-- 
-- /Since: 2.18/
markupParseContextGetUserData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> m (Ptr ())
    -- ^ __Returns:__ the provided user_data. The returned data belongs to
    --     the markup context and will be freed when
    --     'GI.GLib.Structs.MarkupParseContext.markupParseContextFree' is called.
markupParseContextGetUserData :: MarkupParseContext -> m (Ptr ())
markupParseContextGetUserData context :: MarkupParseContext
context = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    Ptr ()
result <- Ptr MarkupParseContext -> IO (Ptr ())
g_markup_parse_context_get_user_data Ptr MarkupParseContext
context'
    MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextGetUserDataMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo MarkupParseContextGetUserDataMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextGetUserData

#endif

-- method MarkupParseContext::parse
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "MarkupParseContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParseContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "chunk of text to parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text_len"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of @text in bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_markup_parse_context_parse" g_markup_parse_context_parse :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    CString ->                              -- text : TBasicType TUTF8
    Int64 ->                                -- text_len : TBasicType TInt64
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Feed some data to the t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'.
-- 
-- The data need not be valid UTF-8; an error will be signaled if
-- it\'s invalid. The data need not be an entire document; you can
-- feed a document into the parser incrementally, via multiple calls
-- to this function. Typically, as you receive data from a network
-- connection or file, you feed each received chunk of data into this
-- function, aborting the process if an error occurs. Once an error
-- is reported, no further data may be fed to the t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext';
-- all errors are fatal.
markupParseContextParse ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> T.Text
    -- ^ /@text@/: chunk of text to parse
    -> Int64
    -- ^ /@textLen@/: length of /@text@/ in bytes
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
markupParseContextParse :: MarkupParseContext -> Text -> Int64 -> m ()
markupParseContextParse context :: MarkupParseContext
context text :: Text
text textLen :: Int64
textLen = 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 MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    CString
text' <- Text -> IO CString
textToCString Text
text
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr MarkupParseContext
-> CString -> Int64 -> Ptr (Ptr GError) -> IO CInt
g_markup_parse_context_parse Ptr MarkupParseContext
context' CString
text' Int64
textLen
        MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
     )

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextParseMethodInfo
instance (signature ~ (T.Text -> Int64 -> m ()), MonadIO m) => O.MethodInfo MarkupParseContextParseMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextParse

#endif

-- method MarkupParseContext::pop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "MarkupParseContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParseContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_markup_parse_context_pop" g_markup_parse_context_pop :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    IO (Ptr ())

-- | Completes the process of a temporary sub-parser redirection.
-- 
-- This function exists to collect the user_data allocated by a
-- matching call to 'GI.GLib.Structs.MarkupParseContext.markupParseContextPush'. It must be called
-- in the end_element handler corresponding to the start_element
-- handler during which 'GI.GLib.Structs.MarkupParseContext.markupParseContextPush' was called.
-- You must not call this function from the error callback -- the
-- /@userData@/ is provided directly to the callback in that case.
-- 
-- This function is not intended to be directly called by users
-- interested in invoking subparsers. Instead, it is intended to
-- be used by the subparsers themselves to implement a higher-level
-- interface.
-- 
-- /Since: 2.18/
markupParseContextPop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> m (Ptr ())
    -- ^ __Returns:__ the user data passed to 'GI.GLib.Structs.MarkupParseContext.markupParseContextPush'
markupParseContextPop :: MarkupParseContext -> m (Ptr ())
markupParseContextPop context :: MarkupParseContext
context = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    Ptr ()
result <- Ptr MarkupParseContext -> IO (Ptr ())
g_markup_parse_context_pop Ptr MarkupParseContext
context'
    MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextPopMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.MethodInfo MarkupParseContextPopMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextPop

#endif

-- method MarkupParseContext::push
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "MarkupParseContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParseContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parser"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MarkupParser" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParser" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to #GMarkupParser functions"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_markup_parse_context_push" g_markup_parse_context_push :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    Ptr GLib.MarkupParser.MarkupParser ->   -- parser : TInterface (Name {namespace = "GLib", name = "MarkupParser"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Temporarily redirects markup data to a sub-parser.
-- 
-- This function may only be called from the start_element handler of
-- a t'GI.GLib.Structs.MarkupParser.MarkupParser'. It must be matched with a corresponding call to
-- 'GI.GLib.Structs.MarkupParseContext.markupParseContextPop' in the matching end_element handler
-- (except in the case that the parser aborts due to an error).
-- 
-- All tags, text and other data between the matching tags is
-- redirected to the subparser given by /@parser@/. /@userData@/ is used
-- as the user_data for that parser. /@userData@/ is also passed to the
-- error callback in the event that an error occurs. This includes
-- errors that occur in subparsers of the subparser.
-- 
-- The end tag matching the start tag for which this call was made is
-- handled by the previous parser (which is given its own user_data)
-- which is why 'GI.GLib.Structs.MarkupParseContext.markupParseContextPop' is provided to allow \"one
-- last access\" to the /@userData@/ provided to this function. In the
-- case of error, the /@userData@/ provided here is passed directly to
-- the error callback of the subparser and 'GI.GLib.Structs.MarkupParseContext.markupParseContextPop'
-- should not be called. In either case, if /@userData@/ was allocated
-- then it ought to be freed from both of these locations.
-- 
-- This function is not intended to be directly called by users
-- interested in invoking subparsers. Instead, it is intended to be
-- used by the subparsers themselves to implement a higher-level
-- interface.
-- 
-- As an example, see the following implementation of a simple
-- parser that counts the number of tags encountered.
-- 
-- 
-- === /C code/
-- >
-- >typedef struct
-- >{
-- >  gint tag_count;
-- >} CounterData;
-- >
-- >static void
-- >counter_start_element (GMarkupParseContext  *context,
-- >                       const gchar          *element_name,
-- >                       const gchar         **attribute_names,
-- >                       const gchar         **attribute_values,
-- >                       gpointer              user_data,
-- >                       GError              **error)
-- >{
-- >  CounterData *data = user_data;
-- >
-- >  data->tag_count++;
-- >}
-- >
-- >static void
-- >counter_error (GMarkupParseContext *context,
-- >               GError              *error,
-- >               gpointer             user_data)
-- >{
-- >  CounterData *data = user_data;
-- >
-- >  g_slice_free (CounterData, data);
-- >}
-- >
-- >static GMarkupParser counter_subparser =
-- >{
-- >  counter_start_element,
-- >  NULL,
-- >  NULL,
-- >  NULL,
-- >  counter_error
-- >};
-- 
-- 
-- In order to allow this parser to be easily used as a subparser, the
-- following interface is provided:
-- 
-- 
-- === /C code/
-- >
-- >void
-- >start_counting (GMarkupParseContext *context)
-- >{
-- >  CounterData *data = g_slice_new (CounterData);
-- >
-- >  data->tag_count = 0;
-- >  g_markup_parse_context_push (context, &counter_subparser, data);
-- >}
-- >
-- >gint
-- >end_counting (GMarkupParseContext *context)
-- >{
-- >  CounterData *data = g_markup_parse_context_pop (context);
-- >  int result;
-- >
-- >  result = data->tag_count;
-- >  g_slice_free (CounterData, data);
-- >
-- >  return result;
-- >}
-- 
-- 
-- The subparser would then be used as follows:
-- 
-- 
-- === /C code/
-- >
-- >static void start_element (context, element_name, ...)
-- >{
-- >  if (strcmp (element_name, "count-these") == 0)
-- >    start_counting (context);
-- >
-- >  // else, handle other tags...
-- >}
-- >
-- >static void end_element (context, element_name, ...)
-- >{
-- >  if (strcmp (element_name, "count-these") == 0)
-- >    g_print ("Counted %d tags\n", end_counting (context));
-- >
-- >  // else, handle other tags...
-- >}
-- 
-- 
-- /Since: 2.18/
markupParseContextPush ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> GLib.MarkupParser.MarkupParser
    -- ^ /@parser@/: a t'GI.GLib.Structs.MarkupParser.MarkupParser'
    -> Ptr ()
    -- ^ /@userData@/: user data to pass to t'GI.GLib.Structs.MarkupParser.MarkupParser' functions
    -> m ()
markupParseContextPush :: MarkupParseContext -> MarkupParser -> Ptr () -> m ()
markupParseContextPush context :: MarkupParseContext
context parser :: MarkupParser
parser userData :: Ptr ()
userData = 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 MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    Ptr MarkupParser
parser' <- MarkupParser -> IO (Ptr MarkupParser)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParser
parser
    Ptr MarkupParseContext -> Ptr MarkupParser -> DestroyNotify
g_markup_parse_context_push Ptr MarkupParseContext
context' Ptr MarkupParser
parser' Ptr ()
userData
    MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
    MarkupParser -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParser
parser
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextPushMethodInfo
instance (signature ~ (GLib.MarkupParser.MarkupParser -> Ptr () -> m ()), MonadIO m) => O.MethodInfo MarkupParseContextPushMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextPush

#endif

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

foreign import ccall "g_markup_parse_context_ref" g_markup_parse_context_ref :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    IO (Ptr MarkupParseContext)

-- | Increases the reference count of /@context@/.
-- 
-- /Since: 2.36/
markupParseContextRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> m MarkupParseContext
    -- ^ __Returns:__ the same /@context@/
markupParseContextRef :: MarkupParseContext -> m MarkupParseContext
markupParseContextRef context :: MarkupParseContext
context = IO MarkupParseContext -> m MarkupParseContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MarkupParseContext -> m MarkupParseContext)
-> IO MarkupParseContext -> m MarkupParseContext
forall a b. (a -> b) -> a -> b
$ do
    Ptr MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    Ptr MarkupParseContext
result <- Ptr MarkupParseContext -> IO (Ptr MarkupParseContext)
g_markup_parse_context_ref Ptr MarkupParseContext
context'
    Text -> Ptr MarkupParseContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "markupParseContextRef" Ptr MarkupParseContext
result
    MarkupParseContext
result' <- ((ManagedPtr MarkupParseContext -> MarkupParseContext)
-> Ptr MarkupParseContext -> IO MarkupParseContext
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr MarkupParseContext -> MarkupParseContext
MarkupParseContext) Ptr MarkupParseContext
result
    MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
    MarkupParseContext -> IO MarkupParseContext
forall (m :: * -> *) a. Monad m => a -> m a
return MarkupParseContext
result'

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextRefMethodInfo
instance (signature ~ (m MarkupParseContext), MonadIO m) => O.MethodInfo MarkupParseContextRefMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextRef

#endif

-- method MarkupParseContext::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "MarkupParseContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMarkupParseContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_markup_parse_context_unref" g_markup_parse_context_unref :: 
    Ptr MarkupParseContext ->               -- context : TInterface (Name {namespace = "GLib", name = "MarkupParseContext"})
    IO ()

-- | Decreases the reference count of /@context@/.  When its reference count
-- drops to 0, it is freed.
-- 
-- /Since: 2.36/
markupParseContextUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MarkupParseContext
    -- ^ /@context@/: a t'GI.GLib.Structs.MarkupParseContext.MarkupParseContext'
    -> m ()
markupParseContextUnref :: MarkupParseContext -> m ()
markupParseContextUnref context :: MarkupParseContext
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 MarkupParseContext
context' <- MarkupParseContext -> IO (Ptr MarkupParseContext)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MarkupParseContext
context
    Ptr MarkupParseContext -> IO ()
g_markup_parse_context_unref Ptr MarkupParseContext
context'
    MarkupParseContext -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MarkupParseContext
context
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MarkupParseContextUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo MarkupParseContextUnrefMethodInfo MarkupParseContext signature where
    overloadedMethod = markupParseContextUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveMarkupParseContextMethod (t :: Symbol) (o :: *) :: * where
    ResolveMarkupParseContextMethod "endParse" o = MarkupParseContextEndParseMethodInfo
    ResolveMarkupParseContextMethod "free" o = MarkupParseContextFreeMethodInfo
    ResolveMarkupParseContextMethod "parse" o = MarkupParseContextParseMethodInfo
    ResolveMarkupParseContextMethod "pop" o = MarkupParseContextPopMethodInfo
    ResolveMarkupParseContextMethod "push" o = MarkupParseContextPushMethodInfo
    ResolveMarkupParseContextMethod "ref" o = MarkupParseContextRefMethodInfo
    ResolveMarkupParseContextMethod "unref" o = MarkupParseContextUnrefMethodInfo
    ResolveMarkupParseContextMethod "getElement" o = MarkupParseContextGetElementMethodInfo
    ResolveMarkupParseContextMethod "getUserData" o = MarkupParseContextGetUserDataMethodInfo
    ResolveMarkupParseContextMethod l o = O.MethodResolutionFailed l o

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

#endif