{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GdkContentSerializer@ is used to serialize content for
-- inter-application data transfers.
-- 
-- The @GdkContentSerializer@ transforms an object that is identified
-- by a GType into a serialized form (i.e. a byte stream) that is
-- identified by a mime type.
-- 
-- GTK provides serializers and deserializers for common data types
-- such as text, colors, images or file lists. To register your own
-- serialization functions, use 'GI.Gdk.Functions.contentRegisterSerializer'.
-- 
-- Also see t'GI.Gdk.Objects.ContentDeserializer.ContentDeserializer'.

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

module GI.Gdk.Objects.ContentSerializer
    ( 

-- * Exported types
    ContentSerializer(..)                   ,
    IsContentSerializer                     ,
    toContentSerializer                     ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isTagged]("GI.Gio.Interfaces.AsyncResult#g:method:isTagged"), [legacyPropagateError]("GI.Gio.Interfaces.AsyncResult#g:method:legacyPropagateError"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [returnError]("GI.Gdk.Objects.ContentSerializer#g:method:returnError"), [returnSuccess]("GI.Gdk.Objects.ContentSerializer#g:method:returnSuccess"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCancellable]("GI.Gdk.Objects.ContentSerializer#g:method:getCancellable"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getGtype]("GI.Gdk.Objects.ContentSerializer#g:method:getGtype"), [getMimeType]("GI.Gdk.Objects.ContentSerializer#g:method:getMimeType"), [getOutputStream]("GI.Gdk.Objects.ContentSerializer#g:method:getOutputStream"), [getPriority]("GI.Gdk.Objects.ContentSerializer#g:method:getPriority"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSourceObject]("GI.Gio.Interfaces.AsyncResult#g:method:getSourceObject"), [getTaskData]("GI.Gdk.Objects.ContentSerializer#g:method:getTaskData"), [getUserData]("GI.Gdk.Objects.ContentSerializer#g:method:getUserData"), [getValue]("GI.Gdk.Objects.ContentSerializer#g:method:getValue").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTaskData]("GI.Gdk.Objects.ContentSerializer#g:method:setTaskData").

#if defined(ENABLE_OVERLOADING)
    ResolveContentSerializerMethod          ,
#endif

-- ** getCancellable #method:getCancellable#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerGetCancellableMethodInfo,
#endif
    contentSerializerGetCancellable         ,


-- ** getGtype #method:getGtype#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerGetGtypeMethodInfo     ,
#endif
    contentSerializerGetGtype               ,


-- ** getMimeType #method:getMimeType#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerGetMimeTypeMethodInfo  ,
#endif
    contentSerializerGetMimeType            ,


-- ** getOutputStream #method:getOutputStream#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerGetOutputStreamMethodInfo,
#endif
    contentSerializerGetOutputStream        ,


-- ** getPriority #method:getPriority#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerGetPriorityMethodInfo  ,
#endif
    contentSerializerGetPriority            ,


-- ** getTaskData #method:getTaskData#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerGetTaskDataMethodInfo  ,
#endif
    contentSerializerGetTaskData            ,


-- ** getUserData #method:getUserData#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerGetUserDataMethodInfo  ,
#endif
    contentSerializerGetUserData            ,


-- ** getValue #method:getValue#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerGetValueMethodInfo     ,
#endif
    contentSerializerGetValue               ,


-- ** returnError #method:returnError#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerReturnErrorMethodInfo  ,
#endif
    contentSerializerReturnError            ,


-- ** returnSuccess #method:returnSuccess#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerReturnSuccessMethodInfo,
#endif
    contentSerializerReturnSuccess          ,


-- ** setTaskData #method:setTaskData#

#if defined(ENABLE_OVERLOADING)
    ContentSerializerSetTaskDataMethodInfo  ,
#endif
    contentSerializerSetTaskData            ,




    ) 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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream

#else
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream

#endif

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

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

foreign import ccall "gdk_content_serializer_get_type"
    c_gdk_content_serializer_get_type :: IO B.Types.GType

instance B.Types.TypedObject ContentSerializer where
    glibType :: IO GType
glibType = IO GType
c_gdk_content_serializer_get_type

instance B.Types.GObject ContentSerializer

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

instance O.HasParentTypes ContentSerializer
type instance O.ParentTypes ContentSerializer = '[GObject.Object.Object, Gio.AsyncResult.AsyncResult]

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

-- | Convert 'ContentSerializer' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe ContentSerializer) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_content_serializer_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ContentSerializer -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ContentSerializer
P.Nothing = Ptr GValue -> Ptr ContentSerializer -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ContentSerializer
forall a. Ptr a
FP.nullPtr :: FP.Ptr ContentSerializer)
    gvalueSet_ Ptr GValue
gv (P.Just ContentSerializer
obj) = ContentSerializer -> (Ptr ContentSerializer -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ContentSerializer
obj (Ptr GValue -> Ptr ContentSerializer -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ContentSerializer)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr ContentSerializer)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ContentSerializer)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newObject ContentSerializer ptr
        else return P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveContentSerializerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveContentSerializerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveContentSerializerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveContentSerializerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveContentSerializerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveContentSerializerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveContentSerializerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveContentSerializerMethod "isTagged" o = Gio.AsyncResult.AsyncResultIsTaggedMethodInfo
    ResolveContentSerializerMethod "legacyPropagateError" o = Gio.AsyncResult.AsyncResultLegacyPropagateErrorMethodInfo
    ResolveContentSerializerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveContentSerializerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveContentSerializerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveContentSerializerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveContentSerializerMethod "returnError" o = ContentSerializerReturnErrorMethodInfo
    ResolveContentSerializerMethod "returnSuccess" o = ContentSerializerReturnSuccessMethodInfo
    ResolveContentSerializerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveContentSerializerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveContentSerializerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveContentSerializerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveContentSerializerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveContentSerializerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveContentSerializerMethod "getCancellable" o = ContentSerializerGetCancellableMethodInfo
    ResolveContentSerializerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveContentSerializerMethod "getGtype" o = ContentSerializerGetGtypeMethodInfo
    ResolveContentSerializerMethod "getMimeType" o = ContentSerializerGetMimeTypeMethodInfo
    ResolveContentSerializerMethod "getOutputStream" o = ContentSerializerGetOutputStreamMethodInfo
    ResolveContentSerializerMethod "getPriority" o = ContentSerializerGetPriorityMethodInfo
    ResolveContentSerializerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveContentSerializerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveContentSerializerMethod "getSourceObject" o = Gio.AsyncResult.AsyncResultGetSourceObjectMethodInfo
    ResolveContentSerializerMethod "getTaskData" o = ContentSerializerGetTaskDataMethodInfo
    ResolveContentSerializerMethod "getUserData" o = ContentSerializerGetUserDataMethodInfo
    ResolveContentSerializerMethod "getValue" o = ContentSerializerGetValueMethodInfo
    ResolveContentSerializerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveContentSerializerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveContentSerializerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveContentSerializerMethod "setTaskData" o = ContentSerializerSetTaskDataMethodInfo
    ResolveContentSerializerMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveContentSerializerMethod t ContentSerializer, O.OverloadedMethod info ContentSerializer p) => OL.IsLabel t (ContentSerializer -> 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 ~ ResolveContentSerializerMethod t ContentSerializer, O.OverloadedMethod info ContentSerializer p, R.HasField t ContentSerializer p) => R.HasField t ContentSerializer p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveContentSerializerMethod t ContentSerializer, O.OverloadedMethodInfo info ContentSerializer) => OL.IsLabel t (O.MethodProxy info ContentSerializer) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ContentSerializer
type instance O.AttributeList ContentSerializer = ContentSerializerAttributeList
type ContentSerializerAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ContentSerializer = ContentSerializerSignalList
type ContentSerializerSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method ContentSerializer::get_cancellable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Cancellable" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_get_cancellable" gdk_content_serializer_get_cancellable :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO (Ptr Gio.Cancellable.Cancellable)

-- | Gets the cancellable for the current operation.
-- 
-- This is the @GCancellable@ that was passed to [func/@contentSerializeAsync@/].
contentSerializerGetCancellable ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m (Maybe Gio.Cancellable.Cancellable)
    -- ^ __Returns:__ the cancellable for the current operation
contentSerializerGetCancellable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m (Maybe Cancellable)
contentSerializerGetCancellable a
serializer = IO (Maybe Cancellable) -> m (Maybe Cancellable)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Cancellable) -> m (Maybe Cancellable))
-> IO (Maybe Cancellable) -> m (Maybe Cancellable)
forall a b. (a -> b) -> a -> b
$ do
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    result <- gdk_content_serializer_get_cancellable serializer'
    maybeResult <- convertIfNonNull result $ \Ptr Cancellable
result' -> do
        result'' <- ((ManagedPtr Cancellable -> Cancellable)
-> Ptr Cancellable -> IO Cancellable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Cancellable -> Cancellable
Gio.Cancellable.Cancellable) Ptr Cancellable
result'
        return result''
    touchManagedPtr serializer
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data ContentSerializerGetCancellableMethodInfo
instance (signature ~ (m (Maybe Gio.Cancellable.Cancellable)), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerGetCancellableMethodInfo a signature where
    overloadedMethod = contentSerializerGetCancellable

instance O.OverloadedMethodInfo ContentSerializerGetCancellableMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerGetCancellable",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerGetCancellable"
        })


#endif

-- method ContentSerializer::get_gtype
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_get_gtype" gdk_content_serializer_get_gtype :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO CGType

-- | Gets the @GType@ to of the object to serialize.
contentSerializerGetGtype ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m GType
    -- ^ __Returns:__ the @GType@ for the current operation
contentSerializerGetGtype :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m GType
contentSerializerGetGtype a
serializer = 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
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    result <- gdk_content_serializer_get_gtype serializer'
    let result' = CGType -> GType
GType CGType
result
    touchManagedPtr serializer
    return result'

#if defined(ENABLE_OVERLOADING)
data ContentSerializerGetGtypeMethodInfo
instance (signature ~ (m GType), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerGetGtypeMethodInfo a signature where
    overloadedMethod = contentSerializerGetGtype

instance O.OverloadedMethodInfo ContentSerializerGetGtypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerGetGtype",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerGetGtype"
        })


#endif

-- method ContentSerializer::get_mime_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_get_mime_type" gdk_content_serializer_get_mime_type :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO CString

-- | Gets the mime type to serialize to.
contentSerializerGetMimeType ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m T.Text
    -- ^ __Returns:__ the mime type for the current operation
contentSerializerGetMimeType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m Text
contentSerializerGetMimeType a
serializer = 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
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    result <- gdk_content_serializer_get_mime_type serializer'
    checkUnexpectedReturnNULL "contentSerializerGetMimeType" result
    result' <- cstringToText result
    touchManagedPtr serializer
    return result'

#if defined(ENABLE_OVERLOADING)
data ContentSerializerGetMimeTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerGetMimeTypeMethodInfo a signature where
    overloadedMethod = contentSerializerGetMimeType

instance O.OverloadedMethodInfo ContentSerializerGetMimeTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerGetMimeType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerGetMimeType"
        })


#endif

-- method ContentSerializer::get_output_stream
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "OutputStream" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_get_output_stream" gdk_content_serializer_get_output_stream :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO (Ptr Gio.OutputStream.OutputStream)

-- | Gets the output stream for the current operation.
-- 
-- This is the stream that was passed to [func/@contentSerializeAsync@/].
contentSerializerGetOutputStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m Gio.OutputStream.OutputStream
    -- ^ __Returns:__ the output stream for the current operation
contentSerializerGetOutputStream :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m OutputStream
contentSerializerGetOutputStream a
serializer = IO OutputStream -> m OutputStream
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OutputStream -> m OutputStream)
-> IO OutputStream -> m OutputStream
forall a b. (a -> b) -> a -> b
$ do
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    result <- gdk_content_serializer_get_output_stream serializer'
    checkUnexpectedReturnNULL "contentSerializerGetOutputStream" result
    result' <- (newObject Gio.OutputStream.OutputStream) result
    touchManagedPtr serializer
    return result'

#if defined(ENABLE_OVERLOADING)
data ContentSerializerGetOutputStreamMethodInfo
instance (signature ~ (m Gio.OutputStream.OutputStream), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerGetOutputStreamMethodInfo a signature where
    overloadedMethod = contentSerializerGetOutputStream

instance O.OverloadedMethodInfo ContentSerializerGetOutputStreamMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerGetOutputStream",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerGetOutputStream"
        })


#endif

-- method ContentSerializer::get_priority
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_get_priority" gdk_content_serializer_get_priority :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO Int32

-- | Gets the I\/O priority for the current operation.
-- 
-- This is the priority that was passed to [func/@contentSerializeAsync@/].
contentSerializerGetPriority ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m Int32
    -- ^ __Returns:__ the I\/O priority for the current operation
contentSerializerGetPriority :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m Int32
contentSerializerGetPriority a
serializer = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    result <- gdk_content_serializer_get_priority serializer'
    touchManagedPtr serializer
    return result

#if defined(ENABLE_OVERLOADING)
data ContentSerializerGetPriorityMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerGetPriorityMethodInfo a signature where
    overloadedMethod = contentSerializerGetPriority

instance O.OverloadedMethodInfo ContentSerializerGetPriorityMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerGetPriority",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerGetPriority"
        })


#endif

-- method ContentSerializer::get_task_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_get_task_data" gdk_content_serializer_get_task_data :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO (Ptr ())

-- | Gets the data that was associated with the current operation.
-- 
-- See 'GI.Gdk.Objects.ContentSerializer.contentSerializerSetTaskData'.
contentSerializerGetTaskData ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m (Ptr ())
    -- ^ __Returns:__ the task data for /@serializer@/
contentSerializerGetTaskData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m (Ptr ())
contentSerializerGetTaskData a
serializer = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
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
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    result <- gdk_content_serializer_get_task_data serializer'
    touchManagedPtr serializer
    return result

#if defined(ENABLE_OVERLOADING)
data ContentSerializerGetTaskDataMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerGetTaskDataMethodInfo a signature where
    overloadedMethod = contentSerializerGetTaskData

instance O.OverloadedMethodInfo ContentSerializerGetTaskDataMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerGetTaskData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerGetTaskData"
        })


#endif

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

foreign import ccall "gdk_content_serializer_get_user_data" gdk_content_serializer_get_user_data :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO (Ptr ())

-- | Gets the user data that was passed when the serializer was registered.
contentSerializerGetUserData ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m (Ptr ())
    -- ^ __Returns:__ the user data for this serializer
contentSerializerGetUserData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m (Ptr ())
contentSerializerGetUserData a
serializer = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
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
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    result <- gdk_content_serializer_get_user_data serializer'
    touchManagedPtr serializer
    return result

#if defined(ENABLE_OVERLOADING)
data ContentSerializerGetUserDataMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerGetUserDataMethodInfo a signature where
    overloadedMethod = contentSerializerGetUserData

instance O.OverloadedMethodInfo ContentSerializerGetUserDataMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerGetUserData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerGetUserData"
        })


#endif

-- method ContentSerializer::get_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TGValue
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_get_value" gdk_content_serializer_get_value :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO (Ptr GValue)

-- | Gets the @GValue@ to read the object to serialize from.
contentSerializerGetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m GValue
    -- ^ __Returns:__ the @GValue@ for the current operation
contentSerializerGetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m GValue
contentSerializerGetValue a
serializer = IO GValue -> m GValue
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ do
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    result <- gdk_content_serializer_get_value serializer'
    checkUnexpectedReturnNULL "contentSerializerGetValue" result
    result' <- B.GValue.newGValueFromPtr result
    touchManagedPtr serializer
    return result'

#if defined(ENABLE_OVERLOADING)
data ContentSerializerGetValueMethodInfo
instance (signature ~ (m GValue), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerGetValueMethodInfo a signature where
    overloadedMethod = contentSerializerGetValue

instance O.OverloadedMethodInfo ContentSerializerGetValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerGetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerGetValue"
        })


#endif

-- method ContentSerializer::return_error
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "error"
--           , argType = TError
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GError`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_return_error" gdk_content_serializer_return_error :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    Ptr GError ->                           -- error : TError
    IO ()

-- | Indicate that the serialization has ended with an error.
-- 
-- This function consumes /@error@/.
contentSerializerReturnError ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> GError
    -- ^ /@error@/: a @GError@
    -> m ()
contentSerializerReturnError :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> GError -> m ()
contentSerializerReturnError a
serializer GError
error_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    error_' <- B.ManagedPtr.disownBoxed error_
    gdk_content_serializer_return_error serializer' error_'
    touchManagedPtr serializer
    touchManagedPtr error_
    return ()

#if defined(ENABLE_OVERLOADING)
data ContentSerializerReturnErrorMethodInfo
instance (signature ~ (GError -> m ()), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerReturnErrorMethodInfo a signature where
    overloadedMethod = contentSerializerReturnError

instance O.OverloadedMethodInfo ContentSerializerReturnErrorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerReturnError",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerReturnError"
        })


#endif

-- method ContentSerializer::return_success
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_return_success" gdk_content_serializer_return_success :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    IO ()

-- | Indicate that the serialization has been successfully completed.
contentSerializerReturnSuccess ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> m ()
contentSerializerReturnSuccess :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> m ()
contentSerializerReturnSuccess a
serializer = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    gdk_content_serializer_return_success serializer'
    touchManagedPtr serializer
    return ()

#if defined(ENABLE_OVERLOADING)
data ContentSerializerReturnSuccessMethodInfo
instance (signature ~ (m ()), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerReturnSuccessMethodInfo a signature where
    overloadedMethod = contentSerializerReturnSuccess

instance O.OverloadedMethodInfo ContentSerializerReturnSuccessMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerReturnSuccess",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerReturnSuccess"
        })


#endif

-- method ContentSerializer::set_task_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "serializer"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentSerializer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentSerializer`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to associate with this operation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destroy notify for @data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_serializer_set_task_data" gdk_content_serializer_set_task_data :: 
    Ptr ContentSerializer ->                -- serializer : TInterface (Name {namespace = "Gdk", name = "ContentSerializer"})
    Ptr () ->                               -- data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Associate data with the current serialization operation.
contentSerializerSetTaskData ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentSerializer a) =>
    a
    -- ^ /@serializer@/: a @GdkContentSerializer@
    -> Ptr ()
    -- ^ /@data@/: data to associate with this operation
    -> GLib.Callbacks.DestroyNotify
    -- ^ /@notify@/: destroy notify for /@data@/
    -> m ()
contentSerializerSetTaskData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContentSerializer a) =>
a -> Ptr () -> DestroyNotify -> m ()
contentSerializerSetTaskData a
serializer Ptr ()
data_ DestroyNotify
notify = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    serializer' <- a -> IO (Ptr ContentSerializer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
serializer
    ptrnotify <- callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
    notify' <- GLib.Callbacks.mk_DestroyNotify (GLib.Callbacks.wrap_DestroyNotify (Just ptrnotify) notify)
    poke ptrnotify notify'
    gdk_content_serializer_set_task_data serializer' data_ notify'
    touchManagedPtr serializer
    return ()

#if defined(ENABLE_OVERLOADING)
data ContentSerializerSetTaskDataMethodInfo
instance (signature ~ (Ptr () -> GLib.Callbacks.DestroyNotify -> m ()), MonadIO m, IsContentSerializer a) => O.OverloadedMethod ContentSerializerSetTaskDataMethodInfo a signature where
    overloadedMethod = contentSerializerSetTaskData

instance O.OverloadedMethodInfo ContentSerializerSetTaskDataMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.ContentSerializer.contentSerializerSetTaskData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Objects-ContentSerializer.html#v:contentSerializerSetTaskData"
        })


#endif