{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.OSTree.Objects.ContentWriter
    ( 

-- * Exported types
    ContentWriter(..)                       ,
    IsContentWriter                         ,
    toContentWriter                         ,


 -- * 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"), [clearPending]("GI.Gio.Objects.OutputStream#g:method:clearPending"), [close]("GI.Gio.Objects.OutputStream#g:method:close"), [closeAsync]("GI.Gio.Objects.OutputStream#g:method:closeAsync"), [closeFinish]("GI.Gio.Objects.OutputStream#g:method:closeFinish"), [finish]("GI.OSTree.Objects.ContentWriter#g:method:finish"), [flush]("GI.Gio.Objects.OutputStream#g:method:flush"), [flushAsync]("GI.Gio.Objects.OutputStream#g:method:flushAsync"), [flushFinish]("GI.Gio.Objects.OutputStream#g:method:flushFinish"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasPending]("GI.Gio.Objects.OutputStream#g:method:hasPending"), [isClosed]("GI.Gio.Objects.OutputStream#g:method:isClosed"), [isClosing]("GI.Gio.Objects.OutputStream#g:method:isClosing"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [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"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [splice]("GI.Gio.Objects.OutputStream#g:method:splice"), [spliceAsync]("GI.Gio.Objects.OutputStream#g:method:spliceAsync"), [spliceFinish]("GI.Gio.Objects.OutputStream#g:method:spliceFinish"), [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"), [write]("GI.Gio.Objects.OutputStream#g:method:write"), [writeAll]("GI.Gio.Objects.OutputStream#g:method:writeAll"), [writeAllAsync]("GI.Gio.Objects.OutputStream#g:method:writeAllAsync"), [writeAllFinish]("GI.Gio.Objects.OutputStream#g:method:writeAllFinish"), [writeAsync]("GI.Gio.Objects.OutputStream#g:method:writeAsync"), [writeBytes]("GI.Gio.Objects.OutputStream#g:method:writeBytes"), [writeBytesAsync]("GI.Gio.Objects.OutputStream#g:method:writeBytesAsync"), [writeBytesFinish]("GI.Gio.Objects.OutputStream#g:method:writeBytesFinish"), [writeFinish]("GI.Gio.Objects.OutputStream#g:method:writeFinish"), [writev]("GI.Gio.Objects.OutputStream#g:method:writev"), [writevAll]("GI.Gio.Objects.OutputStream#g:method:writevAll"), [writevAllAsync]("GI.Gio.Objects.OutputStream#g:method:writevAllAsync"), [writevAllFinish]("GI.Gio.Objects.OutputStream#g:method:writevAllFinish"), [writevAsync]("GI.Gio.Objects.OutputStream#g:method:writevAsync"), [writevFinish]("GI.Gio.Objects.OutputStream#g:method:writevFinish").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setPending]("GI.Gio.Objects.OutputStream#g:method:setPending"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveContentWriterMethod              ,
#endif

-- ** finish #method:finish#

#if defined(ENABLE_OVERLOADING)
    ContentWriterFinishMethodInfo           ,
#endif
    contentWriterFinish                     ,




    ) 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.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.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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream

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

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

foreign import ccall "ostree_content_writer_get_type"
    c_ostree_content_writer_get_type :: IO B.Types.GType

instance B.Types.TypedObject ContentWriter where
    glibType :: IO GType
glibType = IO GType
c_ostree_content_writer_get_type

instance B.Types.GObject ContentWriter

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

instance O.HasParentTypes ContentWriter
type instance O.ParentTypes ContentWriter = '[Gio.OutputStream.OutputStream, GObject.Object.Object]

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

-- | Convert 'ContentWriter' 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 ContentWriter) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ostree_content_writer_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ContentWriter -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ContentWriter
P.Nothing = Ptr GValue -> Ptr ContentWriter -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ContentWriter
forall a. Ptr a
FP.nullPtr :: FP.Ptr ContentWriter)
    gvalueSet_ Ptr GValue
gv (P.Just ContentWriter
obj) = ContentWriter -> (Ptr ContentWriter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ContentWriter
obj (Ptr GValue -> Ptr ContentWriter -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ContentWriter)
gvalueGet_ Ptr GValue
gv = do
        Ptr ContentWriter
ptr <- Ptr GValue -> IO (Ptr ContentWriter)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ContentWriter)
        if Ptr ContentWriter
ptr Ptr ContentWriter -> Ptr ContentWriter -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ContentWriter
forall a. Ptr a
FP.nullPtr
        then ContentWriter -> Maybe ContentWriter
forall a. a -> Maybe a
P.Just (ContentWriter -> Maybe ContentWriter)
-> IO ContentWriter -> IO (Maybe ContentWriter)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ContentWriter -> ContentWriter)
-> Ptr ContentWriter -> IO ContentWriter
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ContentWriter -> ContentWriter
ContentWriter Ptr ContentWriter
ptr
        else Maybe ContentWriter -> IO (Maybe ContentWriter)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ContentWriter
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveContentWriterMethod (t :: Symbol) (o :: *) :: * where
    ResolveContentWriterMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveContentWriterMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveContentWriterMethod "clearPending" o = Gio.OutputStream.OutputStreamClearPendingMethodInfo
    ResolveContentWriterMethod "close" o = Gio.OutputStream.OutputStreamCloseMethodInfo
    ResolveContentWriterMethod "closeAsync" o = Gio.OutputStream.OutputStreamCloseAsyncMethodInfo
    ResolveContentWriterMethod "closeFinish" o = Gio.OutputStream.OutputStreamCloseFinishMethodInfo
    ResolveContentWriterMethod "finish" o = ContentWriterFinishMethodInfo
    ResolveContentWriterMethod "flush" o = Gio.OutputStream.OutputStreamFlushMethodInfo
    ResolveContentWriterMethod "flushAsync" o = Gio.OutputStream.OutputStreamFlushAsyncMethodInfo
    ResolveContentWriterMethod "flushFinish" o = Gio.OutputStream.OutputStreamFlushFinishMethodInfo
    ResolveContentWriterMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveContentWriterMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveContentWriterMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveContentWriterMethod "hasPending" o = Gio.OutputStream.OutputStreamHasPendingMethodInfo
    ResolveContentWriterMethod "isClosed" o = Gio.OutputStream.OutputStreamIsClosedMethodInfo
    ResolveContentWriterMethod "isClosing" o = Gio.OutputStream.OutputStreamIsClosingMethodInfo
    ResolveContentWriterMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveContentWriterMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveContentWriterMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveContentWriterMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveContentWriterMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveContentWriterMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveContentWriterMethod "splice" o = Gio.OutputStream.OutputStreamSpliceMethodInfo
    ResolveContentWriterMethod "spliceAsync" o = Gio.OutputStream.OutputStreamSpliceAsyncMethodInfo
    ResolveContentWriterMethod "spliceFinish" o = Gio.OutputStream.OutputStreamSpliceFinishMethodInfo
    ResolveContentWriterMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveContentWriterMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveContentWriterMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveContentWriterMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveContentWriterMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveContentWriterMethod "write" o = Gio.OutputStream.OutputStreamWriteMethodInfo
    ResolveContentWriterMethod "writeAll" o = Gio.OutputStream.OutputStreamWriteAllMethodInfo
    ResolveContentWriterMethod "writeAllAsync" o = Gio.OutputStream.OutputStreamWriteAllAsyncMethodInfo
    ResolveContentWriterMethod "writeAllFinish" o = Gio.OutputStream.OutputStreamWriteAllFinishMethodInfo
    ResolveContentWriterMethod "writeAsync" o = Gio.OutputStream.OutputStreamWriteAsyncMethodInfo
    ResolveContentWriterMethod "writeBytes" o = Gio.OutputStream.OutputStreamWriteBytesMethodInfo
    ResolveContentWriterMethod "writeBytesAsync" o = Gio.OutputStream.OutputStreamWriteBytesAsyncMethodInfo
    ResolveContentWriterMethod "writeBytesFinish" o = Gio.OutputStream.OutputStreamWriteBytesFinishMethodInfo
    ResolveContentWriterMethod "writeFinish" o = Gio.OutputStream.OutputStreamWriteFinishMethodInfo
    ResolveContentWriterMethod "writev" o = Gio.OutputStream.OutputStreamWritevMethodInfo
    ResolveContentWriterMethod "writevAll" o = Gio.OutputStream.OutputStreamWritevAllMethodInfo
    ResolveContentWriterMethod "writevAllAsync" o = Gio.OutputStream.OutputStreamWritevAllAsyncMethodInfo
    ResolveContentWriterMethod "writevAllFinish" o = Gio.OutputStream.OutputStreamWritevAllFinishMethodInfo
    ResolveContentWriterMethod "writevAsync" o = Gio.OutputStream.OutputStreamWritevAsyncMethodInfo
    ResolveContentWriterMethod "writevFinish" o = Gio.OutputStream.OutputStreamWritevFinishMethodInfo
    ResolveContentWriterMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveContentWriterMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveContentWriterMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveContentWriterMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveContentWriterMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveContentWriterMethod "setPending" o = Gio.OutputStream.OutputStreamSetPendingMethodInfo
    ResolveContentWriterMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveContentWriterMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ContentWriter = ContentWriterSignalList
type ContentWriterSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method ContentWriter::finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "ContentWriter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Writer" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_content_writer_finish" ostree_content_writer_finish :: 
    Ptr ContentWriter ->                    -- self : TInterface (Name {namespace = "OSTree", name = "ContentWriter"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Complete the object write and return the checksum.
contentWriterFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsContentWriter a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@self@/: Writer
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m T.Text
    -- ^ __Returns:__ Checksum, or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
contentWriterFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsContentWriter a, IsCancellable b) =>
a -> Maybe b -> m Text
contentWriterFinish a
self Maybe b
cancellable = 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 ContentWriter
self' <- a -> IO (Ptr ContentWriter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr ContentWriter
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO CString
ostree_content_writer_finish Ptr ContentWriter
self' Ptr Cancellable
maybeCancellable
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"contentWriterFinish" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data ContentWriterFinishMethodInfo
instance (signature ~ (Maybe (b) -> m T.Text), MonadIO m, IsContentWriter a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod ContentWriterFinishMethodInfo a signature where
    overloadedMethod = contentWriterFinish

instance O.OverloadedMethodInfo ContentWriterFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.ContentWriter.contentWriterFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-ContentWriter.html#v:contentWriterFinish"
        })


#endif