{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.InputStream
(
InputStream(..) ,
IsInputStream ,
toInputStream ,
#if defined(ENABLE_OVERLOADING)
ResolveInputStreamMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
InputStreamClearPendingMethodInfo ,
#endif
inputStreamClearPending ,
#if defined(ENABLE_OVERLOADING)
InputStreamCloseMethodInfo ,
#endif
inputStreamClose ,
#if defined(ENABLE_OVERLOADING)
InputStreamCloseAsyncMethodInfo ,
#endif
inputStreamCloseAsync ,
#if defined(ENABLE_OVERLOADING)
InputStreamCloseFinishMethodInfo ,
#endif
inputStreamCloseFinish ,
#if defined(ENABLE_OVERLOADING)
InputStreamHasPendingMethodInfo ,
#endif
inputStreamHasPending ,
#if defined(ENABLE_OVERLOADING)
InputStreamIsClosedMethodInfo ,
#endif
inputStreamIsClosed ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadMethodInfo ,
#endif
inputStreamRead ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadAllMethodInfo ,
#endif
inputStreamReadAll ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadAllAsyncMethodInfo ,
#endif
inputStreamReadAllAsync ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadAllFinishMethodInfo ,
#endif
inputStreamReadAllFinish ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadAsyncMethodInfo ,
#endif
inputStreamReadAsync ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadBytesMethodInfo ,
#endif
inputStreamReadBytes ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadBytesAsyncMethodInfo ,
#endif
inputStreamReadBytesAsync ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadBytesFinishMethodInfo ,
#endif
inputStreamReadBytesFinish ,
#if defined(ENABLE_OVERLOADING)
InputStreamReadFinishMethodInfo ,
#endif
inputStreamReadFinish ,
#if defined(ENABLE_OVERLOADING)
InputStreamSetPendingMethodInfo ,
#endif
inputStreamSetPending ,
#if defined(ENABLE_OVERLOADING)
InputStreamSkipMethodInfo ,
#endif
inputStreamSkip ,
#if defined(ENABLE_OVERLOADING)
InputStreamSkipAsyncMethodInfo ,
#endif
inputStreamSkipAsync ,
#if defined(ENABLE_OVERLOADING)
InputStreamSkipFinishMethodInfo ,
#endif
inputStreamSkipFinish ,
) 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
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.Objects.Cancellable as Gio.Cancellable
newtype InputStream = InputStream (SP.ManagedPtr InputStream)
deriving (InputStream -> InputStream -> Bool
(InputStream -> InputStream -> Bool)
-> (InputStream -> InputStream -> Bool) -> Eq InputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputStream -> InputStream -> Bool
$c/= :: InputStream -> InputStream -> Bool
== :: InputStream -> InputStream -> Bool
$c== :: InputStream -> InputStream -> Bool
Eq)
instance SP.ManagedPtrNewtype InputStream where
toManagedPtr :: InputStream -> ManagedPtr InputStream
toManagedPtr (InputStream ManagedPtr InputStream
p) = ManagedPtr InputStream
p
foreign import ccall "g_input_stream_get_type"
c_g_input_stream_get_type :: IO B.Types.GType
instance B.Types.TypedObject InputStream where
glibType :: IO GType
glibType = IO GType
c_g_input_stream_get_type
instance B.Types.GObject InputStream
instance B.GValue.IsGValue InputStream where
toGValue :: InputStream -> IO GValue
toGValue InputStream
o = do
GType
gtype <- IO GType
c_g_input_stream_get_type
InputStream -> (Ptr InputStream -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr InputStream
o (GType
-> (GValue -> Ptr InputStream -> IO ())
-> Ptr InputStream
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr InputStream -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO InputStream
fromGValue GValue
gv = do
Ptr InputStream
ptr <- GValue -> IO (Ptr InputStream)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr InputStream)
(ManagedPtr InputStream -> InputStream)
-> Ptr InputStream -> IO InputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr InputStream -> InputStream
InputStream Ptr InputStream
ptr
class (SP.GObject o, O.IsDescendantOf InputStream o) => IsInputStream o
instance (SP.GObject o, O.IsDescendantOf InputStream o) => IsInputStream o
instance O.HasParentTypes InputStream
type instance O.ParentTypes InputStream = '[GObject.Object.Object]
toInputStream :: (MonadIO m, IsInputStream o) => o -> m InputStream
toInputStream :: o -> m InputStream
toInputStream = IO InputStream -> m InputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputStream -> m InputStream)
-> (o -> IO InputStream) -> o -> m InputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr InputStream -> InputStream) -> o -> IO InputStream
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr InputStream -> InputStream
InputStream
#if defined(ENABLE_OVERLOADING)
type family ResolveInputStreamMethod (t :: Symbol) (o :: *) :: * where
ResolveInputStreamMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveInputStreamMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveInputStreamMethod "clearPending" o = InputStreamClearPendingMethodInfo
ResolveInputStreamMethod "close" o = InputStreamCloseMethodInfo
ResolveInputStreamMethod "closeAsync" o = InputStreamCloseAsyncMethodInfo
ResolveInputStreamMethod "closeFinish" o = InputStreamCloseFinishMethodInfo
ResolveInputStreamMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveInputStreamMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveInputStreamMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveInputStreamMethod "hasPending" o = InputStreamHasPendingMethodInfo
ResolveInputStreamMethod "isClosed" o = InputStreamIsClosedMethodInfo
ResolveInputStreamMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveInputStreamMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveInputStreamMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveInputStreamMethod "read" o = InputStreamReadMethodInfo
ResolveInputStreamMethod "readAll" o = InputStreamReadAllMethodInfo
ResolveInputStreamMethod "readAllAsync" o = InputStreamReadAllAsyncMethodInfo
ResolveInputStreamMethod "readAllFinish" o = InputStreamReadAllFinishMethodInfo
ResolveInputStreamMethod "readAsync" o = InputStreamReadAsyncMethodInfo
ResolveInputStreamMethod "readBytes" o = InputStreamReadBytesMethodInfo
ResolveInputStreamMethod "readBytesAsync" o = InputStreamReadBytesAsyncMethodInfo
ResolveInputStreamMethod "readBytesFinish" o = InputStreamReadBytesFinishMethodInfo
ResolveInputStreamMethod "readFinish" o = InputStreamReadFinishMethodInfo
ResolveInputStreamMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveInputStreamMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveInputStreamMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveInputStreamMethod "skip" o = InputStreamSkipMethodInfo
ResolveInputStreamMethod "skipAsync" o = InputStreamSkipAsyncMethodInfo
ResolveInputStreamMethod "skipFinish" o = InputStreamSkipFinishMethodInfo
ResolveInputStreamMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveInputStreamMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveInputStreamMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveInputStreamMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveInputStreamMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveInputStreamMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveInputStreamMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveInputStreamMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveInputStreamMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveInputStreamMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveInputStreamMethod "setPending" o = InputStreamSetPendingMethodInfo
ResolveInputStreamMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveInputStreamMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveInputStreamMethod t InputStream, O.MethodInfo info InputStream p) => OL.IsLabel t (InputStream -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList InputStream
type instance O.AttributeList InputStream = InputStreamAttributeList
type InputStreamAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList InputStream = InputStreamSignalList
type InputStreamSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_input_stream_clear_pending" g_input_stream_clear_pending ::
Ptr InputStream ->
IO ()
inputStreamClearPending ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a) =>
a
-> m ()
inputStreamClearPending :: a -> m ()
inputStreamClearPending a
stream = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr InputStream -> IO ()
g_input_stream_clear_pending Ptr InputStream
stream'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data InputStreamClearPendingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsInputStream a) => O.MethodInfo InputStreamClearPendingMethodInfo a signature where
overloadedMethod = inputStreamClearPending
#endif
foreign import ccall "g_input_stream_close" g_input_stream_close ::
Ptr InputStream ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
inputStreamClose ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m ()
inputStreamClose :: a -> Maybe b -> m ()
inputStreamClose a
stream Maybe b
cancellable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
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'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr InputStream -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_input_stream_close Ptr InputStream
stream' 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
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data InputStreamCloseMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamCloseMethodInfo a signature where
overloadedMethod = inputStreamClose
#endif
foreign import ccall "g_input_stream_close_async" g_input_stream_close_async ::
Ptr InputStream ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
inputStreamCloseAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
inputStreamCloseAsync :: a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
inputStreamCloseAsync a
stream Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
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'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr InputStream
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_input_stream_close_async Ptr InputStream
stream' Int32
ioPriority Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
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
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data InputStreamCloseAsyncMethodInfo
instance (signature ~ (Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamCloseAsyncMethodInfo a signature where
overloadedMethod = inputStreamCloseAsync
#endif
foreign import ccall "g_input_stream_close_finish" g_input_stream_close_finish ::
Ptr InputStream ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
inputStreamCloseFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
inputStreamCloseFinish :: a -> b -> m ()
inputStreamCloseFinish a
stream b
result_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr InputStream -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_input_stream_close_finish Ptr InputStream
stream' Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data InputStreamCloseFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo InputStreamCloseFinishMethodInfo a signature where
overloadedMethod = inputStreamCloseFinish
#endif
foreign import ccall "g_input_stream_has_pending" g_input_stream_has_pending ::
Ptr InputStream ->
IO CInt
inputStreamHasPending ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a) =>
a
-> m Bool
inputStreamHasPending :: a -> m Bool
inputStreamHasPending 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 InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
CInt
result <- Ptr InputStream -> IO CInt
g_input_stream_has_pending Ptr InputStream
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 InputStreamHasPendingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInputStream a) => O.MethodInfo InputStreamHasPendingMethodInfo a signature where
overloadedMethod = inputStreamHasPending
#endif
foreign import ccall "g_input_stream_is_closed" g_input_stream_is_closed ::
Ptr InputStream ->
IO CInt
inputStreamIsClosed ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a) =>
a
-> m Bool
inputStreamIsClosed :: a -> m Bool
inputStreamIsClosed 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 InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
CInt
result <- Ptr InputStream -> IO CInt
g_input_stream_is_closed Ptr InputStream
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 InputStreamIsClosedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInputStream a) => O.MethodInfo InputStreamIsClosedMethodInfo a signature where
overloadedMethod = inputStreamIsClosed
#endif
foreign import ccall "g_input_stream_read" g_input_stream_read ::
Ptr InputStream ->
Ptr Word8 ->
Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
inputStreamRead ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> ByteString
-> Maybe (b)
-> m ((Int64, ByteString))
inputStreamRead :: a -> ByteString -> Maybe b -> m (Int64, ByteString)
inputStreamRead a
stream ByteString
buffer Maybe b
cancellable = IO (Int64, ByteString) -> m (Int64, ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int64, ByteString) -> m (Int64, ByteString))
-> IO (Int64, ByteString) -> m (Int64, ByteString)
forall a b. (a -> b) -> a -> b
$ do
let count :: Word64
count = 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
buffer
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
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, ByteString) -> IO () -> IO (Int64, ByteString)
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 InputStream
-> Ptr Word8
-> Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_input_stream_read Ptr InputStream
stream' Ptr Word8
buffer' Word64
count Ptr Cancellable
maybeCancellable
ByteString
buffer'' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
count) Ptr Word8
buffer'
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
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
(Int64, ByteString) -> IO (Int64, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int64
result, ByteString
buffer'')
) (do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
)
#if defined(ENABLE_OVERLOADING)
data InputStreamReadMethodInfo
instance (signature ~ (ByteString -> Maybe (b) -> m ((Int64, ByteString))), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamReadMethodInfo a signature where
overloadedMethod = inputStreamRead
#endif
foreign import ccall "g_input_stream_read_all" g_input_stream_read_all ::
Ptr InputStream ->
Ptr Word8 ->
Word64 ->
Ptr Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
inputStreamReadAll ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> ByteString
-> Maybe (b)
-> m ((ByteString, Word64))
inputStreamReadAll :: a -> ByteString -> Maybe b -> m (ByteString, Word64)
inputStreamReadAll a
stream ByteString
buffer Maybe b
cancellable = IO (ByteString, Word64) -> m (ByteString, Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ByteString, Word64) -> m (ByteString, Word64))
-> IO (ByteString, Word64) -> m (ByteString, Word64)
forall a b. (a -> b) -> a -> b
$ do
let count :: Word64
count = 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
buffer
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
Ptr Word64
bytesRead <- 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 (ByteString, Word64) -> IO () -> IO (ByteString, Word64)
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr InputStream
-> Ptr Word8
-> Word64
-> Ptr Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
g_input_stream_read_all Ptr InputStream
stream' Ptr Word8
buffer' Word64
count Ptr Word64
bytesRead Ptr Cancellable
maybeCancellable
ByteString
buffer'' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
count) Ptr Word8
buffer'
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
Word64
bytesRead' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
bytesRead
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 Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bytesRead
(ByteString, Word64) -> IO (ByteString, Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
buffer'', Word64
bytesRead')
) (do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bytesRead
)
#if defined(ENABLE_OVERLOADING)
data InputStreamReadAllMethodInfo
instance (signature ~ (ByteString -> Maybe (b) -> m ((ByteString, Word64))), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamReadAllMethodInfo a signature where
overloadedMethod = inputStreamReadAll
#endif
foreign import ccall "g_input_stream_read_all_async" g_input_stream_read_all_async ::
Ptr InputStream ->
Ptr Word8 ->
Word64 ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
inputStreamReadAllAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> ByteString
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m (ByteString)
inputStreamReadAllAsync :: a
-> ByteString
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ByteString
inputStreamReadAllAsync a
stream ByteString
buffer Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
let count :: Word64
count = 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
buffer
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
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'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr InputStream
-> Ptr Word8
-> Word64
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_input_stream_read_all_async Ptr InputStream
stream' Ptr Word8
buffer' Word64
count Int32
ioPriority Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
ByteString
buffer'' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
count) Ptr Word8
buffer'
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
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
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
buffer''
#if defined(ENABLE_OVERLOADING)
data InputStreamReadAllAsyncMethodInfo
instance (signature ~ (ByteString -> Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m (ByteString)), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamReadAllAsyncMethodInfo a signature where
overloadedMethod = inputStreamReadAllAsync
#endif
foreign import ccall "g_input_stream_read_all_finish" g_input_stream_read_all_finish ::
Ptr InputStream ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr Word64 ->
Ptr (Ptr GError) ->
IO CInt
inputStreamReadAllFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m (Word64)
inputStreamReadAllFinish :: a -> b -> m Word64
inputStreamReadAllFinish a
stream b
result_ = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
Ptr Word64
bytesRead <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
IO Word64 -> IO () -> IO Word64
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr InputStream
-> Ptr AsyncResult -> Ptr Word64 -> Ptr (Ptr GError) -> IO CInt
g_input_stream_read_all_finish Ptr InputStream
stream' Ptr AsyncResult
result_' Ptr Word64
bytesRead
Word64
bytesRead' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
bytesRead
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bytesRead
Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
bytesRead'
) (do
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bytesRead
)
#if defined(ENABLE_OVERLOADING)
data InputStreamReadAllFinishMethodInfo
instance (signature ~ (b -> m (Word64)), MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo InputStreamReadAllFinishMethodInfo a signature where
overloadedMethod = inputStreamReadAllFinish
#endif
foreign import ccall "g_input_stream_read_async" g_input_stream_read_async ::
Ptr InputStream ->
Ptr Word8 ->
Word64 ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
inputStreamReadAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (ByteString)
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ((Maybe ByteString))
inputStreamReadAsync :: a
-> Maybe ByteString
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m (Maybe ByteString)
inputStreamReadAsync a
stream Maybe ByteString
buffer Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO (Maybe ByteString) -> m (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ByteString) -> m (Maybe ByteString))
-> IO (Maybe ByteString) -> m (Maybe ByteString)
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 InputStream
stream' <- a -> IO (Ptr InputStream)
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'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr InputStream
-> Ptr Word8
-> Word64
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_input_stream_read_async Ptr InputStream
stream' Ptr Word8
maybeBuffer Word64
count Int32
ioPriority Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
Maybe ByteString
maybeMaybeBuffer <- Ptr Word8 -> (Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Word8
maybeBuffer ((Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString))
-> (Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
maybeBuffer' -> do
ByteString
maybeBuffer'' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
count) Ptr Word8
maybeBuffer'
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer'
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
maybeBuffer''
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
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
maybeMaybeBuffer
#if defined(ENABLE_OVERLOADING)
data InputStreamReadAsyncMethodInfo
instance (signature ~ (Maybe (ByteString) -> Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ((Maybe ByteString))), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamReadAsyncMethodInfo a signature where
overloadedMethod = inputStreamReadAsync
#endif
foreign import ccall "g_input_stream_read_bytes" g_input_stream_read_bytes ::
Ptr InputStream ->
Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO (Ptr GLib.Bytes.Bytes)
inputStreamReadBytes ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Word64
-> Maybe (b)
-> m GLib.Bytes.Bytes
inputStreamReadBytes :: a -> Word64 -> Maybe b -> m Bytes
inputStreamReadBytes a
stream Word64
count Maybe b
cancellable = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
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'
IO Bytes -> IO () -> IO Bytes
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Bytes
result <- (Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes))
-> (Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes)
forall a b. (a -> b) -> a -> b
$ Ptr InputStream
-> Word64 -> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr Bytes)
g_input_stream_read_bytes Ptr InputStream
stream' Word64
count Ptr Cancellable
maybeCancellable
Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inputStreamReadBytes" Ptr Bytes
result
Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
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
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data InputStreamReadBytesMethodInfo
instance (signature ~ (Word64 -> Maybe (b) -> m GLib.Bytes.Bytes), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamReadBytesMethodInfo a signature where
overloadedMethod = inputStreamReadBytes
#endif
foreign import ccall "g_input_stream_read_bytes_async" g_input_stream_read_bytes_async ::
Ptr InputStream ->
Word64 ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
inputStreamReadBytesAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Word64
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
inputStreamReadBytesAsync :: a -> Word64 -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
inputStreamReadBytesAsync a
stream Word64
count Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
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'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr InputStream
-> Word64
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_input_stream_read_bytes_async Ptr InputStream
stream' Word64
count Int32
ioPriority Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
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
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data InputStreamReadBytesAsyncMethodInfo
instance (signature ~ (Word64 -> Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamReadBytesAsyncMethodInfo a signature where
overloadedMethod = inputStreamReadBytesAsync
#endif
foreign import ccall "g_input_stream_read_bytes_finish" g_input_stream_read_bytes_finish ::
Ptr InputStream ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr GLib.Bytes.Bytes)
inputStreamReadBytesFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m GLib.Bytes.Bytes
inputStreamReadBytesFinish :: a -> b -> m Bytes
inputStreamReadBytesFinish a
stream b
result_ = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO Bytes -> IO () -> IO Bytes
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Bytes
result <- (Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes))
-> (Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes)
forall a b. (a -> b) -> a -> b
$ Ptr InputStream
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr Bytes)
g_input_stream_read_bytes_finish Ptr InputStream
stream' Ptr AsyncResult
result_'
Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"inputStreamReadBytesFinish" Ptr Bytes
result
Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data InputStreamReadBytesFinishMethodInfo
instance (signature ~ (b -> m GLib.Bytes.Bytes), MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo InputStreamReadBytesFinishMethodInfo a signature where
overloadedMethod = inputStreamReadBytesFinish
#endif
foreign import ccall "g_input_stream_read_finish" g_input_stream_read_finish ::
Ptr InputStream ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO Int64
inputStreamReadFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m Int64
inputStreamReadFinish :: a -> b -> m Int64
inputStreamReadFinish a
stream b
result_ = 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
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
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 InputStream -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO Int64
g_input_stream_read_finish Ptr InputStream
stream' Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data InputStreamReadFinishMethodInfo
instance (signature ~ (b -> m Int64), MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo InputStreamReadFinishMethodInfo a signature where
overloadedMethod = inputStreamReadFinish
#endif
foreign import ccall "g_input_stream_set_pending" g_input_stream_set_pending ::
Ptr InputStream ->
Ptr (Ptr GError) ->
IO CInt
inputStreamSetPending ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a) =>
a
-> m ()
inputStreamSetPending :: a -> m ()
inputStreamSetPending a
stream = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr InputStream -> Ptr (Ptr GError) -> IO CInt
g_input_stream_set_pending Ptr InputStream
stream'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data InputStreamSetPendingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsInputStream a) => O.MethodInfo InputStreamSetPendingMethodInfo a signature where
overloadedMethod = inputStreamSetPending
#endif
foreign import ccall "g_input_stream_skip" g_input_stream_skip ::
Ptr InputStream ->
Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
inputStreamSkip ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Word64
-> Maybe (b)
-> m Int64
inputStreamSkip :: a -> Word64 -> Maybe b -> m Int64
inputStreamSkip a
stream Word64
count 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
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
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'
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 InputStream
-> Word64 -> Ptr Cancellable -> Ptr (Ptr GError) -> IO Int64
g_input_stream_skip Ptr InputStream
stream' 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
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data InputStreamSkipMethodInfo
instance (signature ~ (Word64 -> Maybe (b) -> m Int64), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamSkipMethodInfo a signature where
overloadedMethod = inputStreamSkip
#endif
foreign import ccall "g_input_stream_skip_async" g_input_stream_skip_async ::
Ptr InputStream ->
Word64 ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
inputStreamSkipAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Word64
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
inputStreamSkipAsync :: a -> Word64 -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
inputStreamSkipAsync a
stream Word64
count Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
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'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr InputStream
-> Word64
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_input_stream_skip_async Ptr InputStream
stream' Word64
count Int32
ioPriority Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
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
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data InputStreamSkipAsyncMethodInfo
instance (signature ~ (Word64 -> Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo InputStreamSkipAsyncMethodInfo a signature where
overloadedMethod = inputStreamSkipAsync
#endif
foreign import ccall "g_input_stream_skip_finish" g_input_stream_skip_finish ::
Ptr InputStream ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO Int64
inputStreamSkipFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m Int64
inputStreamSkipFinish :: a -> b -> m Int64
inputStreamSkipFinish a
stream b
result_ = 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
Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
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 InputStream -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO Int64
g_input_stream_skip_finish Ptr InputStream
stream' Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data InputStreamSkipFinishMethodInfo
instance (signature ~ (b -> m Int64), MonadIO m, IsInputStream a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo InputStreamSkipFinishMethodInfo a signature where
overloadedMethod = inputStreamSkipFinish
#endif