{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.PollableOutputStream
    ( 
    PollableOutputStream(..)                ,
    IsPollableOutputStream                  ,
    toPollableOutputStream                  ,
 
#if defined(ENABLE_OVERLOADING)
    ResolvePollableOutputStreamMethod       ,
#endif
#if defined(ENABLE_OVERLOADING)
    PollableOutputStreamCanPollMethodInfo   ,
#endif
    pollableOutputStreamCanPoll             ,
#if defined(ENABLE_OVERLOADING)
    PollableOutputStreamCreateSourceMethodInfo,
#endif
    pollableOutputStreamCreateSource        ,
#if defined(ENABLE_OVERLOADING)
    PollableOutputStreamIsWritableMethodInfo,
#endif
    pollableOutputStreamIsWritable          ,
#if defined(ENABLE_OVERLOADING)
    PollableOutputStreamWriteNonblockingMethodInfo,
#endif
    pollableOutputStreamWriteNonblocking    ,
#if defined(ENABLE_OVERLOADING)
    PollableOutputStreamWritevNonblockingMethodInfo,
#endif
    pollableOutputStreamWritevNonblocking   ,
    ) 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.GLib.Structs.Source as GLib.Source
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector
newtype PollableOutputStream = PollableOutputStream (SP.ManagedPtr PollableOutputStream)
    deriving (PollableOutputStream -> PollableOutputStream -> Bool
(PollableOutputStream -> PollableOutputStream -> Bool)
-> (PollableOutputStream -> PollableOutputStream -> Bool)
-> Eq PollableOutputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollableOutputStream -> PollableOutputStream -> Bool
$c/= :: PollableOutputStream -> PollableOutputStream -> Bool
== :: PollableOutputStream -> PollableOutputStream -> Bool
$c== :: PollableOutputStream -> PollableOutputStream -> Bool
Eq)
instance SP.ManagedPtrNewtype PollableOutputStream where
    toManagedPtr :: PollableOutputStream -> ManagedPtr PollableOutputStream
toManagedPtr (PollableOutputStream ManagedPtr PollableOutputStream
p) = ManagedPtr PollableOutputStream
p
foreign import ccall "g_pollable_output_stream_get_type"
    c_g_pollable_output_stream_get_type :: IO B.Types.GType
instance B.Types.TypedObject PollableOutputStream where
    glibType :: IO GType
glibType = IO GType
c_g_pollable_output_stream_get_type
instance B.Types.GObject PollableOutputStream
class (SP.GObject o, O.IsDescendantOf PollableOutputStream o) => IsPollableOutputStream o
instance (SP.GObject o, O.IsDescendantOf PollableOutputStream o) => IsPollableOutputStream o
instance O.HasParentTypes PollableOutputStream
type instance O.ParentTypes PollableOutputStream = '[Gio.OutputStream.OutputStream, GObject.Object.Object]
toPollableOutputStream :: (MIO.MonadIO m, IsPollableOutputStream o) => o -> m PollableOutputStream
toPollableOutputStream :: forall (m :: * -> *) o.
(MonadIO m, IsPollableOutputStream o) =>
o -> m PollableOutputStream
toPollableOutputStream = IO PollableOutputStream -> m PollableOutputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PollableOutputStream -> m PollableOutputStream)
-> (o -> IO PollableOutputStream) -> o -> m PollableOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr PollableOutputStream -> PollableOutputStream)
-> o -> IO PollableOutputStream
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr PollableOutputStream -> PollableOutputStream
PollableOutputStream
instance B.GValue.IsGValue (Maybe PollableOutputStream) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_pollable_output_stream_get_type
    gvalueSet_ :: Ptr GValue -> Maybe PollableOutputStream -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PollableOutputStream
P.Nothing = Ptr GValue -> Ptr PollableOutputStream -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr PollableOutputStream
forall a. Ptr a
FP.nullPtr :: FP.Ptr PollableOutputStream)
    gvalueSet_ Ptr GValue
gv (P.Just PollableOutputStream
obj) = PollableOutputStream
-> (Ptr PollableOutputStream -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PollableOutputStream
obj (Ptr GValue -> Ptr PollableOutputStream -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe PollableOutputStream)
gvalueGet_ Ptr GValue
gv = do
        Ptr PollableOutputStream
ptr <- Ptr GValue -> IO (Ptr PollableOutputStream)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr PollableOutputStream)
        if Ptr PollableOutputStream
ptr Ptr PollableOutputStream -> Ptr PollableOutputStream -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr PollableOutputStream
forall a. Ptr a
FP.nullPtr
        then PollableOutputStream -> Maybe PollableOutputStream
forall a. a -> Maybe a
P.Just (PollableOutputStream -> Maybe PollableOutputStream)
-> IO PollableOutputStream -> IO (Maybe PollableOutputStream)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr PollableOutputStream -> PollableOutputStream)
-> Ptr PollableOutputStream -> IO PollableOutputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PollableOutputStream -> PollableOutputStream
PollableOutputStream Ptr PollableOutputStream
ptr
        else Maybe PollableOutputStream -> IO (Maybe PollableOutputStream)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PollableOutputStream
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PollableOutputStream
type instance O.AttributeList PollableOutputStream = PollableOutputStreamAttributeList
type PollableOutputStreamAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolvePollableOutputStreamMethod (t :: Symbol) (o :: *) :: * where
    ResolvePollableOutputStreamMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePollableOutputStreamMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePollableOutputStreamMethod "canPoll" o = PollableOutputStreamCanPollMethodInfo
    ResolvePollableOutputStreamMethod "clearPending" o = Gio.OutputStream.OutputStreamClearPendingMethodInfo
    ResolvePollableOutputStreamMethod "close" o = Gio.OutputStream.OutputStreamCloseMethodInfo
    ResolvePollableOutputStreamMethod "closeAsync" o = Gio.OutputStream.OutputStreamCloseAsyncMethodInfo
    ResolvePollableOutputStreamMethod "closeFinish" o = Gio.OutputStream.OutputStreamCloseFinishMethodInfo
    ResolvePollableOutputStreamMethod "createSource" o = PollableOutputStreamCreateSourceMethodInfo
    ResolvePollableOutputStreamMethod "flush" o = Gio.OutputStream.OutputStreamFlushMethodInfo
    ResolvePollableOutputStreamMethod "flushAsync" o = Gio.OutputStream.OutputStreamFlushAsyncMethodInfo
    ResolvePollableOutputStreamMethod "flushFinish" o = Gio.OutputStream.OutputStreamFlushFinishMethodInfo
    ResolvePollableOutputStreamMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePollableOutputStreamMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePollableOutputStreamMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePollableOutputStreamMethod "hasPending" o = Gio.OutputStream.OutputStreamHasPendingMethodInfo
    ResolvePollableOutputStreamMethod "isClosed" o = Gio.OutputStream.OutputStreamIsClosedMethodInfo
    ResolvePollableOutputStreamMethod "isClosing" o = Gio.OutputStream.OutputStreamIsClosingMethodInfo
    ResolvePollableOutputStreamMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePollableOutputStreamMethod "isWritable" o = PollableOutputStreamIsWritableMethodInfo
    ResolvePollableOutputStreamMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePollableOutputStreamMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePollableOutputStreamMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePollableOutputStreamMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePollableOutputStreamMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePollableOutputStreamMethod "splice" o = Gio.OutputStream.OutputStreamSpliceMethodInfo
    ResolvePollableOutputStreamMethod "spliceAsync" o = Gio.OutputStream.OutputStreamSpliceAsyncMethodInfo
    ResolvePollableOutputStreamMethod "spliceFinish" o = Gio.OutputStream.OutputStreamSpliceFinishMethodInfo
    ResolvePollableOutputStreamMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePollableOutputStreamMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePollableOutputStreamMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePollableOutputStreamMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePollableOutputStreamMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePollableOutputStreamMethod "write" o = Gio.OutputStream.OutputStreamWriteMethodInfo
    ResolvePollableOutputStreamMethod "writeAll" o = Gio.OutputStream.OutputStreamWriteAllMethodInfo
    ResolvePollableOutputStreamMethod "writeAllAsync" o = Gio.OutputStream.OutputStreamWriteAllAsyncMethodInfo
    ResolvePollableOutputStreamMethod "writeAllFinish" o = Gio.OutputStream.OutputStreamWriteAllFinishMethodInfo
    ResolvePollableOutputStreamMethod "writeAsync" o = Gio.OutputStream.OutputStreamWriteAsyncMethodInfo
    ResolvePollableOutputStreamMethod "writeBytes" o = Gio.OutputStream.OutputStreamWriteBytesMethodInfo
    ResolvePollableOutputStreamMethod "writeBytesAsync" o = Gio.OutputStream.OutputStreamWriteBytesAsyncMethodInfo
    ResolvePollableOutputStreamMethod "writeBytesFinish" o = Gio.OutputStream.OutputStreamWriteBytesFinishMethodInfo
    ResolvePollableOutputStreamMethod "writeFinish" o = Gio.OutputStream.OutputStreamWriteFinishMethodInfo
    ResolvePollableOutputStreamMethod "writeNonblocking" o = PollableOutputStreamWriteNonblockingMethodInfo
    ResolvePollableOutputStreamMethod "writev" o = Gio.OutputStream.OutputStreamWritevMethodInfo
    ResolvePollableOutputStreamMethod "writevAll" o = Gio.OutputStream.OutputStreamWritevAllMethodInfo
    ResolvePollableOutputStreamMethod "writevAllAsync" o = Gio.OutputStream.OutputStreamWritevAllAsyncMethodInfo
    ResolvePollableOutputStreamMethod "writevAllFinish" o = Gio.OutputStream.OutputStreamWritevAllFinishMethodInfo
    ResolvePollableOutputStreamMethod "writevAsync" o = Gio.OutputStream.OutputStreamWritevAsyncMethodInfo
    ResolvePollableOutputStreamMethod "writevFinish" o = Gio.OutputStream.OutputStreamWritevFinishMethodInfo
    ResolvePollableOutputStreamMethod "writevNonblocking" o = PollableOutputStreamWritevNonblockingMethodInfo
    ResolvePollableOutputStreamMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePollableOutputStreamMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePollableOutputStreamMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePollableOutputStreamMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePollableOutputStreamMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePollableOutputStreamMethod "setPending" o = Gio.OutputStream.OutputStreamSetPendingMethodInfo
    ResolvePollableOutputStreamMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePollableOutputStreamMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePollableOutputStreamMethod t PollableOutputStream, O.OverloadedMethod info PollableOutputStream p) => OL.IsLabel t (PollableOutputStream -> 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 ~ ResolvePollableOutputStreamMethod t PollableOutputStream, O.OverloadedMethod info PollableOutputStream p, R.HasField t PollableOutputStream p) => R.HasField t PollableOutputStream p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePollableOutputStreamMethod t PollableOutputStream, O.OverloadedMethodInfo info PollableOutputStream) => OL.IsLabel t (O.MethodProxy info PollableOutputStream) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "g_pollable_output_stream_can_poll" g_pollable_output_stream_can_poll :: 
    Ptr PollableOutputStream ->             
    IO CInt
pollableOutputStreamCanPoll ::
    (B.CallStack.HasCallStack, MonadIO m, IsPollableOutputStream a) =>
    a
    
    -> m Bool
    
pollableOutputStreamCanPoll :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPollableOutputStream a) =>
a -> m Bool
pollableOutputStreamCanPoll a
stream = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PollableOutputStream
stream' <- a -> IO (Ptr PollableOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    CInt
result <- Ptr PollableOutputStream -> IO CInt
g_pollable_output_stream_can_poll Ptr PollableOutputStream
stream'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PollableOutputStreamCanPollMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPollableOutputStream a) => O.OverloadedMethod PollableOutputStreamCanPollMethodInfo a signature where
    overloadedMethod = pollableOutputStreamCanPoll
instance O.OverloadedMethodInfo PollableOutputStreamCanPollMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.PollableOutputStream.pollableOutputStreamCanPoll",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-PollableOutputStream.html#v:pollableOutputStreamCanPoll"
        })
#endif
foreign import ccall "g_pollable_output_stream_create_source" g_pollable_output_stream_create_source :: 
    Ptr PollableOutputStream ->             
    Ptr Gio.Cancellable.Cancellable ->      
    IO (Ptr GLib.Source.Source)
pollableOutputStreamCreateSource ::
    (B.CallStack.HasCallStack, MonadIO m, IsPollableOutputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    
    -> Maybe (b)
    
    -> m GLib.Source.Source
    
pollableOutputStreamCreateSource :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPollableOutputStream a,
 IsCancellable b) =>
a -> Maybe b -> m Source
pollableOutputStreamCreateSource a
stream Maybe b
cancellable = IO Source -> m Source
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Source -> m Source) -> IO Source -> m Source
forall a b. (a -> b) -> a -> b
$ do
    Ptr PollableOutputStream
stream' <- a -> IO (Ptr PollableOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    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'
    Ptr Source
result <- Ptr PollableOutputStream -> Ptr Cancellable -> IO (Ptr Source)
g_pollable_output_stream_create_source Ptr PollableOutputStream
stream' Ptr Cancellable
maybeCancellable
    Text -> Ptr Source -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pollableOutputStreamCreateSource" Ptr Source
result
    Source
result' <- ((ManagedPtr Source -> Source) -> Ptr Source -> IO Source
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Source -> Source
GLib.Source.Source) Ptr Source
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    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
    Source -> IO Source
forall (m :: * -> *) a. Monad m => a -> m a
return Source
result'
#if defined(ENABLE_OVERLOADING)
data PollableOutputStreamCreateSourceMethodInfo
instance (signature ~ (Maybe (b) -> m GLib.Source.Source), MonadIO m, IsPollableOutputStream a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod PollableOutputStreamCreateSourceMethodInfo a signature where
    overloadedMethod = pollableOutputStreamCreateSource
instance O.OverloadedMethodInfo PollableOutputStreamCreateSourceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.PollableOutputStream.pollableOutputStreamCreateSource",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-PollableOutputStream.html#v:pollableOutputStreamCreateSource"
        })
#endif
foreign import ccall "g_pollable_output_stream_is_writable" g_pollable_output_stream_is_writable :: 
    Ptr PollableOutputStream ->             
    IO CInt
pollableOutputStreamIsWritable ::
    (B.CallStack.HasCallStack, MonadIO m, IsPollableOutputStream a) =>
    a
    
    -> m Bool
    
    
    
    
pollableOutputStreamIsWritable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPollableOutputStream a) =>
a -> m Bool
pollableOutputStreamIsWritable a
stream = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PollableOutputStream
stream' <- a -> IO (Ptr PollableOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    CInt
result <- Ptr PollableOutputStream -> IO CInt
g_pollable_output_stream_is_writable Ptr PollableOutputStream
stream'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PollableOutputStreamIsWritableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPollableOutputStream a) => O.OverloadedMethod PollableOutputStreamIsWritableMethodInfo a signature where
    overloadedMethod = pollableOutputStreamIsWritable
instance O.OverloadedMethodInfo PollableOutputStreamIsWritableMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.PollableOutputStream.pollableOutputStreamIsWritable",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-PollableOutputStream.html#v:pollableOutputStreamIsWritable"
        })
#endif
foreign import ccall "g_pollable_output_stream_write_nonblocking" g_pollable_output_stream_write_nonblocking :: 
    Ptr PollableOutputStream ->             
    Ptr Word8 ->                            
    Word64 ->                               
    Ptr Gio.Cancellable.Cancellable ->      
    Ptr (Ptr GError) ->                     
    IO Int64
pollableOutputStreamWriteNonblocking ::
    (B.CallStack.HasCallStack, MonadIO m, IsPollableOutputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    
    -> Maybe (ByteString)
    
    
    -> Maybe (b)
    
    -> m Int64
    
    
pollableOutputStreamWriteNonblocking :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPollableOutputStream a,
 IsCancellable b) =>
a -> Maybe ByteString -> Maybe b -> m Int64
pollableOutputStreamWriteNonblocking a
stream Maybe ByteString
buffer Maybe b
cancellable = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    let count :: Word64
count = case Maybe ByteString
buffer of
            Maybe ByteString
Nothing -> Word64
0
            Just ByteString
jBuffer -> Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
jBuffer
    Ptr PollableOutputStream
stream' <- a -> IO (Ptr PollableOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    Ptr Word8
maybeBuffer <- case Maybe ByteString
buffer of
        Maybe ByteString
Nothing -> Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
forall a. Ptr a
nullPtr
        Just ByteString
jBuffer -> do
            Ptr Word8
jBuffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
jBuffer
            Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
jBuffer'
    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 Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
        Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr PollableOutputStream
-> Ptr Word8
-> Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_pollable_output_stream_write_nonblocking Ptr PollableOutputStream
stream' Ptr Word8
maybeBuffer Word64
count Ptr Cancellable
maybeCancellable
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
        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
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer
        Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
     ) (do
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer
     )
#if defined(ENABLE_OVERLOADING)
data PollableOutputStreamWriteNonblockingMethodInfo
instance (signature ~ (Maybe (ByteString) -> Maybe (b) -> m Int64), MonadIO m, IsPollableOutputStream a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod PollableOutputStreamWriteNonblockingMethodInfo a signature where
    overloadedMethod = pollableOutputStreamWriteNonblocking
instance O.OverloadedMethodInfo PollableOutputStreamWriteNonblockingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.PollableOutputStream.pollableOutputStreamWriteNonblocking",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-PollableOutputStream.html#v:pollableOutputStreamWriteNonblocking"
        })
#endif
foreign import ccall "g_pollable_output_stream_writev_nonblocking" g_pollable_output_stream_writev_nonblocking :: 
    Ptr PollableOutputStream ->             
    Ptr Gio.OutputVector.OutputVector ->    
    Word64 ->                               
    Ptr Word64 ->                           
    Ptr Gio.Cancellable.Cancellable ->      
    Ptr (Ptr GError) ->                     
    IO CInt
pollableOutputStreamWritevNonblocking ::
    (B.CallStack.HasCallStack, MonadIO m, IsPollableOutputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    
    -> [Gio.OutputVector.OutputVector]
    
    -> Maybe (b)
    
    -> m ((Gio.Enums.PollableReturn, Word64))
    
    
    
    
pollableOutputStreamWritevNonblocking :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPollableOutputStream a,
 IsCancellable b) =>
a -> [OutputVector] -> Maybe b -> m (PollableReturn, Word64)
pollableOutputStreamWritevNonblocking a
stream [OutputVector]
vectors Maybe b
cancellable = IO (PollableReturn, Word64) -> m (PollableReturn, Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (PollableReturn, Word64) -> m (PollableReturn, Word64))
-> IO (PollableReturn, Word64) -> m (PollableReturn, Word64)
forall a b. (a -> b) -> a -> b
$ do
    let nVectors :: Word64
nVectors = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [OutputVector] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [OutputVector]
vectors
    Ptr PollableOutputStream
stream' <- a -> IO (Ptr PollableOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    [Ptr OutputVector]
vectors' <- (OutputVector -> IO (Ptr OutputVector))
-> [OutputVector] -> IO [Ptr OutputVector]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM OutputVector -> IO (Ptr OutputVector)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [OutputVector]
vectors
    Ptr OutputVector
vectors'' <- Int -> [Ptr OutputVector] -> IO (Ptr OutputVector)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
16 [Ptr OutputVector]
vectors'
    Ptr Word64
bytesWritten <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    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 (PollableReturn, Word64) -> IO () -> IO (PollableReturn, Word64)
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
result <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr PollableOutputStream
-> Ptr OutputVector
-> Word64
-> Ptr Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
g_pollable_output_stream_writev_nonblocking Ptr PollableOutputStream
stream' Ptr OutputVector
vectors'' Word64
nVectors Ptr Word64
bytesWritten Ptr Cancellable
maybeCancellable
        let result' :: PollableReturn
result' = (Int -> PollableReturn
forall a. Enum a => Int -> a
toEnum (Int -> PollableReturn) -> (CInt -> Int) -> CInt -> PollableReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
        Word64
bytesWritten' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
bytesWritten
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
        (OutputVector -> IO ()) -> [OutputVector] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ OutputVector -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [OutputVector]
vectors
        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
        Ptr OutputVector -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr OutputVector
vectors''
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bytesWritten
        (PollableReturn, Word64) -> IO (PollableReturn, Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return (PollableReturn
result', Word64
bytesWritten')
     ) (do
        Ptr OutputVector -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr OutputVector
vectors''
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bytesWritten
     )
#if defined(ENABLE_OVERLOADING)
data PollableOutputStreamWritevNonblockingMethodInfo
instance (signature ~ ([Gio.OutputVector.OutputVector] -> Maybe (b) -> m ((Gio.Enums.PollableReturn, Word64))), MonadIO m, IsPollableOutputStream a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod PollableOutputStreamWritevNonblockingMethodInfo a signature where
    overloadedMethod = pollableOutputStreamWritevNonblocking
instance O.OverloadedMethodInfo PollableOutputStreamWritevNonblockingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.PollableOutputStream.pollableOutputStreamWritevNonblocking",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Interfaces-PollableOutputStream.html#v:pollableOutputStreamWritevNonblocking"
        })
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PollableOutputStream = PollableOutputStreamSignalList
type PollableOutputStreamSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif