{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GFileOutputStream@ provides output streams that write their
-- content to a file.
-- 
-- @GFileOutputStream@ implements t'GI.Gio.Interfaces.Seekable.Seekable', which allows the output
-- stream to jump to arbitrary positions in the file and to truncate
-- the file, provided the filesystem of the file supports these
-- operations.
-- 
-- To find the position of a file output stream, use 'GI.Gio.Interfaces.Seekable.seekableTell'.
-- To find out if a file output stream supports seeking, use
-- 'GI.Gio.Interfaces.Seekable.seekableCanSeek'.To position a file output stream, use
-- 'GI.Gio.Interfaces.Seekable.seekableSeek'. To find out if a file output stream supports
-- truncating, use 'GI.Gio.Interfaces.Seekable.seekableCanTruncate'. To truncate a file output
-- stream, use 'GI.Gio.Interfaces.Seekable.seekableTruncate'.

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

module GI.Gio.Objects.FileOutputStream
    ( 

-- * Exported types
    FileOutputStream(..)                    ,
    IsFileOutputStream                      ,
    toFileOutputStream                      ,


 -- * 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"), [canSeek]("GI.Gio.Interfaces.Seekable#g:method:canSeek"), [canTruncate]("GI.Gio.Interfaces.Seekable#g:method:canTruncate"), [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"), [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"), [queryInfo]("GI.Gio.Objects.FileOutputStream#g:method:queryInfo"), [queryInfoAsync]("GI.Gio.Objects.FileOutputStream#g:method:queryInfoAsync"), [queryInfoFinish]("GI.Gio.Objects.FileOutputStream#g:method:queryInfoFinish"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [seek]("GI.Gio.Interfaces.Seekable#g:method:seek"), [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"), [tell]("GI.Gio.Interfaces.Seekable#g:method:tell"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [truncate]("GI.Gio.Interfaces.Seekable#g:method:truncate"), [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"), [getEtag]("GI.Gio.Objects.FileOutputStream#g:method:getEtag"), [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)
    ResolveFileOutputStreamMethod           ,
#endif

-- ** getEtag #method:getEtag#

#if defined(ENABLE_OVERLOADING)
    FileOutputStreamGetEtagMethodInfo       ,
#endif
    fileOutputStreamGetEtag                 ,


-- ** queryInfo #method:queryInfo#

#if defined(ENABLE_OVERLOADING)
    FileOutputStreamQueryInfoMethodInfo     ,
#endif
    fileOutputStreamQueryInfo               ,


-- ** queryInfoAsync #method:queryInfoAsync#

#if defined(ENABLE_OVERLOADING)
    FileOutputStreamQueryInfoAsyncMethodInfo,
#endif
    fileOutputStreamQueryInfoAsync          ,


-- ** queryInfoFinish #method:queryInfoFinish#

#if defined(ENABLE_OVERLOADING)
    FileOutputStreamQueryInfoFinishMethodInfo,
#endif
    fileOutputStreamQueryInfoFinish         ,




    ) 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.GLib.Enums as GLib.Enums
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GLib.Structs.TimeVal as GLib.TimeVal
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Seekable as Gio.Seekable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.FileInfo as Gio.FileInfo
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import {-# SOURCE #-} qualified GI.Gio.Structs.FileAttributeMatcher as Gio.FileAttributeMatcher
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Seekable as Gio.Seekable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.FileInfo as Gio.FileInfo
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream

#endif

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

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

foreign import ccall "g_file_output_stream_get_type"
    c_g_file_output_stream_get_type :: IO B.Types.GType

instance B.Types.TypedObject FileOutputStream where
    glibType :: IO GType
glibType = IO GType
c_g_file_output_stream_get_type

instance B.Types.GObject FileOutputStream

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

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

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

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

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

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method FileOutputStream::get_etag
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileOutputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileOutputStream."
--                 , 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 "g_file_output_stream_get_etag" g_file_output_stream_get_etag :: 
    Ptr FileOutputStream ->                 -- stream : TInterface (Name {namespace = "Gio", name = "FileOutputStream"})
    IO CString

-- | Gets the entity tag for the file when it has been written.
-- This must be called after the stream has been written
-- and closed, as the etag can change while writing.
fileOutputStreamGetEtag ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileOutputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.FileOutputStream.FileOutputStream'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the entity tag for the stream.
fileOutputStreamGetEtag :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileOutputStream a) =>
a -> m (Maybe Text)
fileOutputStreamGetEtag a
stream = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    stream' <- a -> IO (Ptr FileOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    result <- g_file_output_stream_get_etag stream'
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        freeMem result'
        return result''
    touchManagedPtr stream
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data FileOutputStreamGetEtagMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsFileOutputStream a) => O.OverloadedMethod FileOutputStreamGetEtagMethodInfo a signature where
    overloadedMethod = fileOutputStreamGetEtag

instance O.OverloadedMethodInfo FileOutputStreamGetEtagMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileOutputStream.fileOutputStreamGetEtag",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-FileOutputStream.html#v:fileOutputStreamGetEtag"
        })


#endif

-- method FileOutputStream::query_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileOutputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileOutputStream."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attributes"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a file attribute query string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional #GCancellable object, %NULL to ignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "FileInfo" })
-- throws : True
-- Skip return : False

foreign import ccall "g_file_output_stream_query_info" g_file_output_stream_query_info :: 
    Ptr FileOutputStream ->                 -- stream : TInterface (Name {namespace = "Gio", name = "FileOutputStream"})
    CString ->                              -- attributes : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.FileInfo.FileInfo)

-- | Queries a file output stream for the given /@attributes@/.
-- This function blocks while querying the stream. For the asynchronous
-- version of this function, see 'GI.Gio.Objects.FileOutputStream.fileOutputStreamQueryInfoAsync'.
-- While the stream is blocked, the stream will set the pending flag
-- internally, and any other operations on the stream will fail with
-- 'GI.Gio.Enums.IOErrorEnumPending'.
-- 
-- Can fail if the stream was already closed (with /@error@/ being set to
-- 'GI.Gio.Enums.IOErrorEnumClosed'), the stream has pending operations (with /@error@/ being
-- set to 'GI.Gio.Enums.IOErrorEnumPending'), or if querying info is not supported for
-- the stream\'s interface (with /@error@/ being set to 'GI.Gio.Enums.IOErrorEnumNotSupported'). In
-- all cases of failure, 'P.Nothing' will be returned.
-- 
-- If /@cancellable@/ is not 'P.Nothing', then the operation can be cancelled by
-- triggering the cancellable object from another thread. If the operation
-- was cancelled, the error 'GI.Gio.Enums.IOErrorEnumCancelled' will be set, and 'P.Nothing' will
-- be returned.
fileOutputStreamQueryInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileOutputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.FileOutputStream.FileOutputStream'.
    -> T.Text
    -- ^ /@attributes@/: a file attribute query string.
    -> Maybe (b)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> m Gio.FileInfo.FileInfo
    -- ^ __Returns:__ a t'GI.Gio.Objects.FileInfo.FileInfo' for the /@stream@/, or 'P.Nothing' on error. /(Can throw 'Data.GI.Base.GError.GError')/
fileOutputStreamQueryInfo :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileOutputStream a, IsCancellable b) =>
a -> Text -> Maybe b -> m FileInfo
fileOutputStreamQueryInfo a
stream Text
attributes Maybe b
cancellable = IO FileInfo -> m FileInfo
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileInfo -> m FileInfo) -> IO FileInfo -> m FileInfo
forall a b. (a -> b) -> a -> b
$ do
    stream' <- a -> IO (Ptr FileOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    attributes' <- textToCString attributes
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_file_output_stream_query_info stream' attributes' maybeCancellable
        checkUnexpectedReturnNULL "fileOutputStreamQueryInfo" result
        result' <- (wrapObject Gio.FileInfo.FileInfo) result
        touchManagedPtr stream
        whenJust cancellable touchManagedPtr
        freeMem attributes'
        return result'
     ) (do
        freeMem attributes'
     )

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

instance O.OverloadedMethodInfo FileOutputStreamQueryInfoMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileOutputStream.fileOutputStreamQueryInfo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-FileOutputStream.html#v:fileOutputStreamQueryInfo"
        })


#endif

-- method FileOutputStream::query_info_async
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileOutputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileOutputStream."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attributes"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a file attribute query string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "io_priority"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the [I/O priority](iface.AsyncResult.html#io-priority) of the\n  request"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional #GCancellable object, %NULL to ignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "callback to call when the request is satisfied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to callback function"
--                 , 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 "g_file_output_stream_query_info_async" g_file_output_stream_query_info_async :: 
    Ptr FileOutputStream ->                 -- stream : TInterface (Name {namespace = "Gio", name = "FileOutputStream"})
    CString ->                              -- attributes : TBasicType TUTF8
    Int32 ->                                -- io_priority : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously queries the /@stream@/ for a t'GI.Gio.Objects.FileInfo.FileInfo'. When completed,
-- /@callback@/ will be called with a t'GI.Gio.Interfaces.AsyncResult.AsyncResult' which can be used to
-- finish the operation with 'GI.Gio.Objects.FileOutputStream.fileOutputStreamQueryInfoFinish'.
-- 
-- For the synchronous version of this function, see
-- 'GI.Gio.Objects.FileOutputStream.fileOutputStreamQueryInfo'.
fileOutputStreamQueryInfoAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileOutputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.FileOutputStream.FileOutputStream'.
    -> T.Text
    -- ^ /@attributes@/: a file attribute query string.
    -> Int32
    -- ^ /@ioPriority@/: the <http://developer.gnome.org/gio/stable/iface.AsyncResult.html#io-priority I/O priority> of the
    --   request
    -> Maybe (b)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: callback to call when the request is satisfied
    -> m ()
fileOutputStreamQueryInfoAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileOutputStream a, IsCancellable b) =>
a -> Text -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
fileOutputStreamQueryInfoAsync a
stream Text
attributes Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = 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
    stream' <- a -> IO (Ptr FileOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    attributes' <- textToCString attributes
    maybeCancellable <- case cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
        Just b
jCancellable -> do
            jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            return jCancellable'
    maybeCallback <- case callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
        Just AsyncReadyCallback
jCallback -> do
            ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
            poke ptrcallback jCallback'
            return jCallback'
    let userData = Ptr a
forall a. Ptr a
nullPtr
    g_file_output_stream_query_info_async stream' attributes' ioPriority maybeCancellable maybeCallback userData
    touchManagedPtr stream
    whenJust cancellable touchManagedPtr
    freeMem attributes'
    return ()

#if defined(ENABLE_OVERLOADING)
data FileOutputStreamQueryInfoAsyncMethodInfo
instance (signature ~ (T.Text -> Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsFileOutputStream a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod FileOutputStreamQueryInfoAsyncMethodInfo a signature where
    overloadedMethod = fileOutputStreamQueryInfoAsync

instance O.OverloadedMethodInfo FileOutputStreamQueryInfoAsyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileOutputStream.fileOutputStreamQueryInfoAsync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-FileOutputStream.html#v:fileOutputStreamQueryInfoAsync"
        })


#endif

-- method FileOutputStream::query_info_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileOutputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileOutputStream."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncResult." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "FileInfo" })
-- throws : True
-- Skip return : False

foreign import ccall "g_file_output_stream_query_info_finish" g_file_output_stream_query_info_finish :: 
    Ptr FileOutputStream ->                 -- stream : TInterface (Name {namespace = "Gio", name = "FileOutputStream"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.FileInfo.FileInfo)

-- | Finalizes the asynchronous query started
-- by 'GI.Gio.Objects.FileOutputStream.fileOutputStreamQueryInfoAsync'.
fileOutputStreamQueryInfoFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileOutputStream a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.FileOutputStream.FileOutputStream'.
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m Gio.FileInfo.FileInfo
    -- ^ __Returns:__ A t'GI.Gio.Objects.FileInfo.FileInfo' for the finished query. /(Can throw 'Data.GI.Base.GError.GError')/
fileOutputStreamQueryInfoFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileOutputStream a, IsAsyncResult b) =>
a -> b -> m FileInfo
fileOutputStreamQueryInfoFinish a
stream b
result_ = IO FileInfo -> m FileInfo
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileInfo -> m FileInfo) -> IO FileInfo -> m FileInfo
forall a b. (a -> b) -> a -> b
$ do
    stream' <- a -> IO (Ptr FileOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    result_' <- unsafeManagedPtrCastPtr result_
    onException (do
        result <- propagateGError $ g_file_output_stream_query_info_finish stream' result_'
        checkUnexpectedReturnNULL "fileOutputStreamQueryInfoFinish" result
        result' <- (wrapObject Gio.FileInfo.FileInfo) result
        touchManagedPtr stream
        touchManagedPtr result_
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data FileOutputStreamQueryInfoFinishMethodInfo
instance (signature ~ (b -> m Gio.FileInfo.FileInfo), MonadIO m, IsFileOutputStream a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod FileOutputStreamQueryInfoFinishMethodInfo a signature where
    overloadedMethod = fileOutputStreamQueryInfoFinish

instance O.OverloadedMethodInfo FileOutputStreamQueryInfoFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileOutputStream.fileOutputStreamQueryInfoFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-FileOutputStream.html#v:fileOutputStreamQueryInfoFinish"
        })


#endif