{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.IOStream
(
IOStream(..) ,
IsIOStream ,
toIOStream ,
noIOStream ,
#if defined(ENABLE_OVERLOADING)
ResolveIOStreamMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
IOStreamClearPendingMethodInfo ,
#endif
iOStreamClearPending ,
#if defined(ENABLE_OVERLOADING)
IOStreamCloseMethodInfo ,
#endif
iOStreamClose ,
#if defined(ENABLE_OVERLOADING)
IOStreamCloseAsyncMethodInfo ,
#endif
iOStreamCloseAsync ,
#if defined(ENABLE_OVERLOADING)
IOStreamCloseFinishMethodInfo ,
#endif
iOStreamCloseFinish ,
#if defined(ENABLE_OVERLOADING)
IOStreamGetInputStreamMethodInfo ,
#endif
iOStreamGetInputStream ,
#if defined(ENABLE_OVERLOADING)
IOStreamGetOutputStreamMethodInfo ,
#endif
iOStreamGetOutputStream ,
#if defined(ENABLE_OVERLOADING)
IOStreamHasPendingMethodInfo ,
#endif
iOStreamHasPending ,
#if defined(ENABLE_OVERLOADING)
IOStreamIsClosedMethodInfo ,
#endif
iOStreamIsClosed ,
#if defined(ENABLE_OVERLOADING)
IOStreamSetPendingMethodInfo ,
#endif
iOStreamSetPending ,
#if defined(ENABLE_OVERLOADING)
IOStreamSpliceAsyncMethodInfo ,
#endif
iOStreamSpliceAsync ,
iOStreamSpliceFinish ,
#if defined(ENABLE_OVERLOADING)
IOStreamClosedPropertyInfo ,
#endif
getIOStreamClosed ,
#if defined(ENABLE_OVERLOADING)
iOStreamClosed ,
#endif
#if defined(ENABLE_OVERLOADING)
IOStreamInputStreamPropertyInfo ,
#endif
getIOStreamInputStream ,
#if defined(ENABLE_OVERLOADING)
iOStreamInputStream ,
#endif
#if defined(ENABLE_OVERLOADING)
IOStreamOutputStreamPropertyInfo ,
#endif
getIOStreamOutputStream ,
#if defined(ENABLE_OVERLOADING)
iOStreamOutputStream ,
#endif
) 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.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 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.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
newtype IOStream = IOStream (ManagedPtr IOStream)
deriving (IOStream -> IOStream -> Bool
(IOStream -> IOStream -> Bool)
-> (IOStream -> IOStream -> Bool) -> Eq IOStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOStream -> IOStream -> Bool
$c/= :: IOStream -> IOStream -> Bool
== :: IOStream -> IOStream -> Bool
$c== :: IOStream -> IOStream -> Bool
Eq)
foreign import ccall "g_io_stream_get_type"
c_g_io_stream_get_type :: IO GType
instance GObject IOStream where
gobjectType :: IO GType
gobjectType = IO GType
c_g_io_stream_get_type
instance B.GValue.IsGValue IOStream where
toGValue :: IOStream -> IO GValue
toGValue o :: IOStream
o = do
GType
gtype <- IO GType
c_g_io_stream_get_type
IOStream -> (Ptr IOStream -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IOStream
o (GType
-> (GValue -> Ptr IOStream -> IO ()) -> Ptr IOStream -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr IOStream -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO IOStream
fromGValue gv :: GValue
gv = do
Ptr IOStream
ptr <- GValue -> IO (Ptr IOStream)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr IOStream)
(ManagedPtr IOStream -> IOStream) -> Ptr IOStream -> IO IOStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr IOStream -> IOStream
IOStream Ptr IOStream
ptr
class (GObject o, O.IsDescendantOf IOStream o) => IsIOStream o
instance (GObject o, O.IsDescendantOf IOStream o) => IsIOStream o
instance O.HasParentTypes IOStream
type instance O.ParentTypes IOStream = '[GObject.Object.Object]
toIOStream :: (MonadIO m, IsIOStream o) => o -> m IOStream
toIOStream :: o -> m IOStream
toIOStream = IO IOStream -> m IOStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOStream -> m IOStream)
-> (o -> IO IOStream) -> o -> m IOStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr IOStream -> IOStream) -> o -> IO IOStream
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr IOStream -> IOStream
IOStream
noIOStream :: Maybe IOStream
noIOStream :: Maybe IOStream
noIOStream = Maybe IOStream
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveIOStreamMethod (t :: Symbol) (o :: *) :: * where
ResolveIOStreamMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveIOStreamMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveIOStreamMethod "clearPending" o = IOStreamClearPendingMethodInfo
ResolveIOStreamMethod "close" o = IOStreamCloseMethodInfo
ResolveIOStreamMethod "closeAsync" o = IOStreamCloseAsyncMethodInfo
ResolveIOStreamMethod "closeFinish" o = IOStreamCloseFinishMethodInfo
ResolveIOStreamMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveIOStreamMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveIOStreamMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveIOStreamMethod "hasPending" o = IOStreamHasPendingMethodInfo
ResolveIOStreamMethod "isClosed" o = IOStreamIsClosedMethodInfo
ResolveIOStreamMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveIOStreamMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveIOStreamMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveIOStreamMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveIOStreamMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveIOStreamMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveIOStreamMethod "spliceAsync" o = IOStreamSpliceAsyncMethodInfo
ResolveIOStreamMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveIOStreamMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveIOStreamMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveIOStreamMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveIOStreamMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveIOStreamMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveIOStreamMethod "getInputStream" o = IOStreamGetInputStreamMethodInfo
ResolveIOStreamMethod "getOutputStream" o = IOStreamGetOutputStreamMethodInfo
ResolveIOStreamMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveIOStreamMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveIOStreamMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveIOStreamMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveIOStreamMethod "setPending" o = IOStreamSetPendingMethodInfo
ResolveIOStreamMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveIOStreamMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveIOStreamMethod t IOStream, O.MethodInfo info IOStream p) => OL.IsLabel t (IOStream -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getIOStreamClosed :: (MonadIO m, IsIOStream o) => o -> m Bool
getIOStreamClosed :: o -> m Bool
getIOStreamClosed obj :: o
obj = 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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "closed"
#if defined(ENABLE_OVERLOADING)
data IOStreamClosedPropertyInfo
instance AttrInfo IOStreamClosedPropertyInfo where
type AttrAllowedOps IOStreamClosedPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint IOStreamClosedPropertyInfo = IsIOStream
type AttrSetTypeConstraint IOStreamClosedPropertyInfo = (~) ()
type AttrTransferTypeConstraint IOStreamClosedPropertyInfo = (~) ()
type AttrTransferType IOStreamClosedPropertyInfo = ()
type AttrGetType IOStreamClosedPropertyInfo = Bool
type AttrLabel IOStreamClosedPropertyInfo = "closed"
type AttrOrigin IOStreamClosedPropertyInfo = IOStream
attrGet = getIOStreamClosed
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getIOStreamInputStream :: (MonadIO m, IsIOStream o) => o -> m Gio.InputStream.InputStream
getIOStreamInputStream :: o -> m InputStream
getIOStreamInputStream obj :: o
obj = IO InputStream -> m InputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputStream -> m InputStream)
-> IO InputStream -> m InputStream
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe InputStream) -> IO InputStream
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getIOStreamInputStream" (IO (Maybe InputStream) -> IO InputStream)
-> IO (Maybe InputStream) -> IO InputStream
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr InputStream -> InputStream)
-> IO (Maybe InputStream)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "input-stream" ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream
#if defined(ENABLE_OVERLOADING)
data IOStreamInputStreamPropertyInfo
instance AttrInfo IOStreamInputStreamPropertyInfo where
type AttrAllowedOps IOStreamInputStreamPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint IOStreamInputStreamPropertyInfo = IsIOStream
type AttrSetTypeConstraint IOStreamInputStreamPropertyInfo = (~) ()
type AttrTransferTypeConstraint IOStreamInputStreamPropertyInfo = (~) ()
type AttrTransferType IOStreamInputStreamPropertyInfo = ()
type AttrGetType IOStreamInputStreamPropertyInfo = Gio.InputStream.InputStream
type AttrLabel IOStreamInputStreamPropertyInfo = "input-stream"
type AttrOrigin IOStreamInputStreamPropertyInfo = IOStream
attrGet = getIOStreamInputStream
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getIOStreamOutputStream :: (MonadIO m, IsIOStream o) => o -> m Gio.OutputStream.OutputStream
getIOStreamOutputStream :: o -> m OutputStream
getIOStreamOutputStream obj :: o
obj = IO OutputStream -> m OutputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OutputStream -> m OutputStream)
-> IO OutputStream -> m OutputStream
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe OutputStream) -> IO OutputStream
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getIOStreamOutputStream" (IO (Maybe OutputStream) -> IO OutputStream)
-> IO (Maybe OutputStream) -> IO OutputStream
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr OutputStream -> OutputStream)
-> IO (Maybe OutputStream)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "output-stream" ManagedPtr OutputStream -> OutputStream
Gio.OutputStream.OutputStream
#if defined(ENABLE_OVERLOADING)
data IOStreamOutputStreamPropertyInfo
instance AttrInfo IOStreamOutputStreamPropertyInfo where
type AttrAllowedOps IOStreamOutputStreamPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint IOStreamOutputStreamPropertyInfo = IsIOStream
type AttrSetTypeConstraint IOStreamOutputStreamPropertyInfo = (~) ()
type AttrTransferTypeConstraint IOStreamOutputStreamPropertyInfo = (~) ()
type AttrTransferType IOStreamOutputStreamPropertyInfo = ()
type AttrGetType IOStreamOutputStreamPropertyInfo = Gio.OutputStream.OutputStream
type AttrLabel IOStreamOutputStreamPropertyInfo = "output-stream"
type AttrOrigin IOStreamOutputStreamPropertyInfo = IOStream
attrGet = getIOStreamOutputStream
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IOStream
type instance O.AttributeList IOStream = IOStreamAttributeList
type IOStreamAttributeList = ('[ '("closed", IOStreamClosedPropertyInfo), '("inputStream", IOStreamInputStreamPropertyInfo), '("outputStream", IOStreamOutputStreamPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
iOStreamClosed :: AttrLabelProxy "closed"
iOStreamClosed = AttrLabelProxy
iOStreamInputStream :: AttrLabelProxy "inputStream"
iOStreamInputStream = AttrLabelProxy
iOStreamOutputStream :: AttrLabelProxy "outputStream"
iOStreamOutputStream = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList IOStream = IOStreamSignalList
type IOStreamSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_io_stream_clear_pending" g_io_stream_clear_pending ::
Ptr IOStream ->
IO ()
iOStreamClearPending ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a) =>
a
-> m ()
iOStreamClearPending :: a -> m ()
iOStreamClearPending stream :: 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 IOStream
stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr IOStream -> IO ()
g_io_stream_clear_pending Ptr IOStream
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 IOStreamClearPendingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIOStream a) => O.MethodInfo IOStreamClearPendingMethodInfo a signature where
overloadedMethod = iOStreamClearPending
#endif
foreign import ccall "g_io_stream_close" g_io_stream_close ::
Ptr IOStream ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
iOStreamClose ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m ()
iOStreamClose :: a -> Maybe b -> m ()
iOStreamClose stream :: a
stream cancellable :: 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 IOStream
stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: 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 IOStream -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_io_stream_close Ptr IOStream
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 IOStreamCloseMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsIOStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo IOStreamCloseMethodInfo a signature where
overloadedMethod = iOStreamClose
#endif
foreign import ccall "g_io_stream_close_async" g_io_stream_close_async ::
Ptr IOStream ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
iOStreamCloseAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
iOStreamCloseAsync :: a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
iOStreamCloseAsync stream :: a
stream ioPriority :: Int32
ioPriority cancellable :: Maybe b
cancellable callback :: 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 IOStream
stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: 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
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 jCallback :: 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 IOStream
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_io_stream_close_async Ptr IOStream
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 IOStreamCloseAsyncMethodInfo
instance (signature ~ (Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsIOStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo IOStreamCloseAsyncMethodInfo a signature where
overloadedMethod = iOStreamCloseAsync
#endif
foreign import ccall "g_io_stream_close_finish" g_io_stream_close_finish ::
Ptr IOStream ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
iOStreamCloseFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
iOStreamCloseFinish :: a -> b -> m ()
iOStreamCloseFinish stream :: a
stream result_ :: 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 IOStream
stream' <- a -> IO (Ptr IOStream)
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 IOStream -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_io_stream_close_finish Ptr IOStream
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 IOStreamCloseFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsIOStream a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo IOStreamCloseFinishMethodInfo a signature where
overloadedMethod = iOStreamCloseFinish
#endif
foreign import ccall "g_io_stream_get_input_stream" g_io_stream_get_input_stream ::
Ptr IOStream ->
IO (Ptr Gio.InputStream.InputStream)
iOStreamGetInputStream ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a) =>
a
-> m Gio.InputStream.InputStream
iOStreamGetInputStream :: a -> m InputStream
iOStreamGetInputStream stream :: a
stream = IO InputStream -> m InputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputStream -> m InputStream)
-> IO InputStream -> m InputStream
forall a b. (a -> b) -> a -> b
$ do
Ptr IOStream
stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr InputStream
result <- Ptr IOStream -> IO (Ptr InputStream)
g_io_stream_get_input_stream Ptr IOStream
stream'
Text -> Ptr InputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "iOStreamGetInputStream" Ptr InputStream
result
InputStream
result' <- ((ManagedPtr InputStream -> InputStream)
-> Ptr InputStream -> IO InputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream) Ptr InputStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
InputStream -> IO InputStream
forall (m :: * -> *) a. Monad m => a -> m a
return InputStream
result'
#if defined(ENABLE_OVERLOADING)
data IOStreamGetInputStreamMethodInfo
instance (signature ~ (m Gio.InputStream.InputStream), MonadIO m, IsIOStream a) => O.MethodInfo IOStreamGetInputStreamMethodInfo a signature where
overloadedMethod = iOStreamGetInputStream
#endif
foreign import ccall "g_io_stream_get_output_stream" g_io_stream_get_output_stream ::
Ptr IOStream ->
IO (Ptr Gio.OutputStream.OutputStream)
iOStreamGetOutputStream ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a) =>
a
-> m Gio.OutputStream.OutputStream
iOStreamGetOutputStream :: a -> m OutputStream
iOStreamGetOutputStream stream :: a
stream = IO OutputStream -> m OutputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OutputStream -> m OutputStream)
-> IO OutputStream -> m OutputStream
forall a b. (a -> b) -> a -> b
$ do
Ptr IOStream
stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr OutputStream
result <- Ptr IOStream -> IO (Ptr OutputStream)
g_io_stream_get_output_stream Ptr IOStream
stream'
Text -> Ptr OutputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "iOStreamGetOutputStream" Ptr OutputStream
result
OutputStream
result' <- ((ManagedPtr OutputStream -> OutputStream)
-> Ptr OutputStream -> IO OutputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr OutputStream -> OutputStream
Gio.OutputStream.OutputStream) Ptr OutputStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
OutputStream -> IO OutputStream
forall (m :: * -> *) a. Monad m => a -> m a
return OutputStream
result'
#if defined(ENABLE_OVERLOADING)
data IOStreamGetOutputStreamMethodInfo
instance (signature ~ (m Gio.OutputStream.OutputStream), MonadIO m, IsIOStream a) => O.MethodInfo IOStreamGetOutputStreamMethodInfo a signature where
overloadedMethod = iOStreamGetOutputStream
#endif
foreign import ccall "g_io_stream_has_pending" g_io_stream_has_pending ::
Ptr IOStream ->
IO CInt
iOStreamHasPending ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a) =>
a
-> m Bool
iOStreamHasPending :: a -> m Bool
iOStreamHasPending stream :: 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 IOStream
stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
CInt
result <- Ptr IOStream -> IO CInt
g_io_stream_has_pending Ptr IOStream
stream'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 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 IOStreamHasPendingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsIOStream a) => O.MethodInfo IOStreamHasPendingMethodInfo a signature where
overloadedMethod = iOStreamHasPending
#endif
foreign import ccall "g_io_stream_is_closed" g_io_stream_is_closed ::
Ptr IOStream ->
IO CInt
iOStreamIsClosed ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a) =>
a
-> m Bool
iOStreamIsClosed :: a -> m Bool
iOStreamIsClosed stream :: 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 IOStream
stream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
CInt
result <- Ptr IOStream -> IO CInt
g_io_stream_is_closed Ptr IOStream
stream'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 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 IOStreamIsClosedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsIOStream a) => O.MethodInfo IOStreamIsClosedMethodInfo a signature where
overloadedMethod = iOStreamIsClosed
#endif
foreign import ccall "g_io_stream_set_pending" g_io_stream_set_pending ::
Ptr IOStream ->
Ptr (Ptr GError) ->
IO CInt
iOStreamSetPending ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a) =>
a
-> m ()
iOStreamSetPending :: a -> m ()
iOStreamSetPending stream :: 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 IOStream
stream' <- a -> IO (Ptr IOStream)
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 IOStream -> Ptr (Ptr GError) -> IO CInt
g_io_stream_set_pending Ptr IOStream
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 IOStreamSetPendingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIOStream a) => O.MethodInfo IOStreamSetPendingMethodInfo a signature where
overloadedMethod = iOStreamSetPending
#endif
foreign import ccall "g_io_stream_splice_async" g_io_stream_splice_async ::
Ptr IOStream ->
Ptr IOStream ->
CUInt ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
iOStreamSpliceAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsIOStream a, IsIOStream b, Gio.Cancellable.IsCancellable c) =>
a
-> b
-> [Gio.Flags.IOStreamSpliceFlags]
-> Int32
-> Maybe (c)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
iOStreamSpliceAsync :: a
-> b
-> [IOStreamSpliceFlags]
-> Int32
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
iOStreamSpliceAsync stream1 :: a
stream1 stream2 :: b
stream2 flags :: [IOStreamSpliceFlags]
flags ioPriority :: Int32
ioPriority cancellable :: Maybe c
cancellable callback :: 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 IOStream
stream1' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream1
Ptr IOStream
stream2' <- b -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
stream2
let flags' :: CUInt
flags' = [IOStreamSpliceFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IOStreamSpliceFlags]
flags
Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
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
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 jCallback :: 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 IOStream
-> Ptr IOStream
-> CUInt
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_io_stream_splice_async Ptr IOStream
stream1' Ptr IOStream
stream2' CUInt
flags' 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
stream1
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
stream2
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IOStreamSpliceAsyncMethodInfo
instance (signature ~ (b -> [Gio.Flags.IOStreamSpliceFlags] -> Int32 -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsIOStream a, IsIOStream b, Gio.Cancellable.IsCancellable c) => O.MethodInfo IOStreamSpliceAsyncMethodInfo a signature where
overloadedMethod = iOStreamSpliceAsync
#endif
foreign import ccall "g_io_stream_splice_finish" g_io_stream_splice_finish ::
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
iOStreamSpliceFinish ::
(B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a) =>
a
-> m ()
iOStreamSpliceFinish :: a -> m ()
iOStreamSpliceFinish result_ :: a
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 AsyncResult
result_' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
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 AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_io_stream_splice_finish Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
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)
#endif