{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.PollableInputStream
(
PollableInputStream(..) ,
IsPollableInputStream ,
toPollableInputStream ,
#if defined(ENABLE_OVERLOADING)
ResolvePollableInputStreamMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PollableInputStreamCanPollMethodInfo ,
#endif
pollableInputStreamCanPoll ,
#if defined(ENABLE_OVERLOADING)
PollableInputStreamCreateSourceMethodInfo,
#endif
pollableInputStreamCreateSource ,
#if defined(ENABLE_OVERLOADING)
PollableInputStreamIsReadableMethodInfo ,
#endif
pollableInputStreamIsReadable ,
#if defined(ENABLE_OVERLOADING)
PollableInputStreamReadNonblockingMethodInfo,
#endif
pollableInputStreamReadNonblocking ,
) 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.Source as GLib.Source
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
newtype PollableInputStream = PollableInputStream (SP.ManagedPtr PollableInputStream)
deriving (PollableInputStream -> PollableInputStream -> Bool
(PollableInputStream -> PollableInputStream -> Bool)
-> (PollableInputStream -> PollableInputStream -> Bool)
-> Eq PollableInputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollableInputStream -> PollableInputStream -> Bool
$c/= :: PollableInputStream -> PollableInputStream -> Bool
== :: PollableInputStream -> PollableInputStream -> Bool
$c== :: PollableInputStream -> PollableInputStream -> Bool
Eq)
instance SP.ManagedPtrNewtype PollableInputStream where
toManagedPtr :: PollableInputStream -> ManagedPtr PollableInputStream
toManagedPtr (PollableInputStream ManagedPtr PollableInputStream
p) = ManagedPtr PollableInputStream
p
foreign import ccall "g_pollable_input_stream_get_type"
c_g_pollable_input_stream_get_type :: IO B.Types.GType
instance B.Types.TypedObject PollableInputStream where
glibType :: IO GType
glibType = IO GType
c_g_pollable_input_stream_get_type
instance B.Types.GObject PollableInputStream
instance B.GValue.IsGValue PollableInputStream where
toGValue :: PollableInputStream -> IO GValue
toGValue PollableInputStream
o = do
GType
gtype <- IO GType
c_g_pollable_input_stream_get_type
PollableInputStream
-> (Ptr PollableInputStream -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PollableInputStream
o (GType
-> (GValue -> Ptr PollableInputStream -> IO ())
-> Ptr PollableInputStream
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr PollableInputStream -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO PollableInputStream
fromGValue GValue
gv = do
Ptr PollableInputStream
ptr <- GValue -> IO (Ptr PollableInputStream)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr PollableInputStream)
(ManagedPtr PollableInputStream -> PollableInputStream)
-> Ptr PollableInputStream -> IO PollableInputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PollableInputStream -> PollableInputStream
PollableInputStream Ptr PollableInputStream
ptr
class (SP.GObject o, O.IsDescendantOf PollableInputStream o) => IsPollableInputStream o
instance (SP.GObject o, O.IsDescendantOf PollableInputStream o) => IsPollableInputStream o
instance O.HasParentTypes PollableInputStream
type instance O.ParentTypes PollableInputStream = '[Gio.InputStream.InputStream, GObject.Object.Object]
toPollableInputStream :: (MonadIO m, IsPollableInputStream o) => o -> m PollableInputStream
toPollableInputStream :: o -> m PollableInputStream
toPollableInputStream = IO PollableInputStream -> m PollableInputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PollableInputStream -> m PollableInputStream)
-> (o -> IO PollableInputStream) -> o -> m PollableInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr PollableInputStream -> PollableInputStream)
-> o -> IO PollableInputStream
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr PollableInputStream -> PollableInputStream
PollableInputStream
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PollableInputStream
type instance O.AttributeList PollableInputStream = PollableInputStreamAttributeList
type PollableInputStreamAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolvePollableInputStreamMethod (t :: Symbol) (o :: *) :: * where
ResolvePollableInputStreamMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolvePollableInputStreamMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolvePollableInputStreamMethod "canPoll" o = PollableInputStreamCanPollMethodInfo
ResolvePollableInputStreamMethod "clearPending" o = Gio.InputStream.InputStreamClearPendingMethodInfo
ResolvePollableInputStreamMethod "close" o = Gio.InputStream.InputStreamCloseMethodInfo
ResolvePollableInputStreamMethod "closeAsync" o = Gio.InputStream.InputStreamCloseAsyncMethodInfo
ResolvePollableInputStreamMethod "closeFinish" o = Gio.InputStream.InputStreamCloseFinishMethodInfo
ResolvePollableInputStreamMethod "createSource" o = PollableInputStreamCreateSourceMethodInfo
ResolvePollableInputStreamMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolvePollableInputStreamMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolvePollableInputStreamMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolvePollableInputStreamMethod "hasPending" o = Gio.InputStream.InputStreamHasPendingMethodInfo
ResolvePollableInputStreamMethod "isClosed" o = Gio.InputStream.InputStreamIsClosedMethodInfo
ResolvePollableInputStreamMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolvePollableInputStreamMethod "isReadable" o = PollableInputStreamIsReadableMethodInfo
ResolvePollableInputStreamMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolvePollableInputStreamMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolvePollableInputStreamMethod "read" o = Gio.InputStream.InputStreamReadMethodInfo
ResolvePollableInputStreamMethod "readAll" o = Gio.InputStream.InputStreamReadAllMethodInfo
ResolvePollableInputStreamMethod "readAllAsync" o = Gio.InputStream.InputStreamReadAllAsyncMethodInfo
ResolvePollableInputStreamMethod "readAllFinish" o = Gio.InputStream.InputStreamReadAllFinishMethodInfo
ResolvePollableInputStreamMethod "readAsync" o = Gio.InputStream.InputStreamReadAsyncMethodInfo
ResolvePollableInputStreamMethod "readBytes" o = Gio.InputStream.InputStreamReadBytesMethodInfo
ResolvePollableInputStreamMethod "readBytesAsync" o = Gio.InputStream.InputStreamReadBytesAsyncMethodInfo
ResolvePollableInputStreamMethod "readBytesFinish" o = Gio.InputStream.InputStreamReadBytesFinishMethodInfo
ResolvePollableInputStreamMethod "readFinish" o = Gio.InputStream.InputStreamReadFinishMethodInfo
ResolvePollableInputStreamMethod "readNonblocking" o = PollableInputStreamReadNonblockingMethodInfo
ResolvePollableInputStreamMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolvePollableInputStreamMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolvePollableInputStreamMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolvePollableInputStreamMethod "skip" o = Gio.InputStream.InputStreamSkipMethodInfo
ResolvePollableInputStreamMethod "skipAsync" o = Gio.InputStream.InputStreamSkipAsyncMethodInfo
ResolvePollableInputStreamMethod "skipFinish" o = Gio.InputStream.InputStreamSkipFinishMethodInfo
ResolvePollableInputStreamMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolvePollableInputStreamMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolvePollableInputStreamMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolvePollableInputStreamMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolvePollableInputStreamMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolvePollableInputStreamMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolvePollableInputStreamMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolvePollableInputStreamMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolvePollableInputStreamMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolvePollableInputStreamMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolvePollableInputStreamMethod "setPending" o = Gio.InputStream.InputStreamSetPendingMethodInfo
ResolvePollableInputStreamMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolvePollableInputStreamMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePollableInputStreamMethod t PollableInputStream, O.MethodInfo info PollableInputStream p) => OL.IsLabel t (PollableInputStream -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "g_pollable_input_stream_can_poll" g_pollable_input_stream_can_poll ::
Ptr PollableInputStream ->
IO CInt
pollableInputStreamCanPoll ::
(B.CallStack.HasCallStack, MonadIO m, IsPollableInputStream a) =>
a
-> m Bool
pollableInputStreamCanPoll :: a -> m Bool
pollableInputStreamCanPoll 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 PollableInputStream
stream' <- a -> IO (Ptr PollableInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
CInt
result <- Ptr PollableInputStream -> IO CInt
g_pollable_input_stream_can_poll Ptr PollableInputStream
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 PollableInputStreamCanPollMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPollableInputStream a) => O.MethodInfo PollableInputStreamCanPollMethodInfo a signature where
overloadedMethod = pollableInputStreamCanPoll
#endif
foreign import ccall "g_pollable_input_stream_create_source" g_pollable_input_stream_create_source ::
Ptr PollableInputStream ->
Ptr Gio.Cancellable.Cancellable ->
IO (Ptr GLib.Source.Source)
pollableInputStreamCreateSource ::
(B.CallStack.HasCallStack, MonadIO m, IsPollableInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m GLib.Source.Source
pollableInputStreamCreateSource :: a -> Maybe b -> m Source
pollableInputStreamCreateSource a
stream Maybe b
cancellable = IO Source -> m Source
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Source -> m Source) -> IO Source -> m Source
forall a b. (a -> b) -> a -> b
$ do
Ptr PollableInputStream
stream' <- a -> IO (Ptr PollableInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
Ptr Source
result <- Ptr PollableInputStream -> Ptr Cancellable -> IO (Ptr Source)
g_pollable_input_stream_create_source Ptr PollableInputStream
stream' Ptr Cancellable
maybeCancellable
Text -> Ptr Source -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pollableInputStreamCreateSource" Ptr Source
result
Source
result' <- ((ManagedPtr Source -> Source) -> Ptr Source -> IO Source
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Source -> Source
GLib.Source.Source) Ptr Source
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Source -> IO Source
forall (m :: * -> *) a. Monad m => a -> m a
return Source
result'
#if defined(ENABLE_OVERLOADING)
data PollableInputStreamCreateSourceMethodInfo
instance (signature ~ (Maybe (b) -> m GLib.Source.Source), MonadIO m, IsPollableInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo PollableInputStreamCreateSourceMethodInfo a signature where
overloadedMethod = pollableInputStreamCreateSource
#endif
foreign import ccall "g_pollable_input_stream_is_readable" g_pollable_input_stream_is_readable ::
Ptr PollableInputStream ->
IO CInt
pollableInputStreamIsReadable ::
(B.CallStack.HasCallStack, MonadIO m, IsPollableInputStream a) =>
a
-> m Bool
pollableInputStreamIsReadable :: a -> m Bool
pollableInputStreamIsReadable 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 PollableInputStream
stream' <- a -> IO (Ptr PollableInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
CInt
result <- Ptr PollableInputStream -> IO CInt
g_pollable_input_stream_is_readable Ptr PollableInputStream
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 PollableInputStreamIsReadableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPollableInputStream a) => O.MethodInfo PollableInputStreamIsReadableMethodInfo a signature where
overloadedMethod = pollableInputStreamIsReadable
#endif
foreign import ccall "g_pollable_input_stream_read_nonblocking" g_pollable_input_stream_read_nonblocking ::
Ptr PollableInputStream ->
Ptr Word8 ->
Word64 ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO Int64
pollableInputStreamReadNonblocking ::
(B.CallStack.HasCallStack, MonadIO m, IsPollableInputStream a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (ByteString)
-> Maybe (b)
-> m Int64
pollableInputStreamReadNonblocking :: a -> Maybe ByteString -> Maybe b -> m Int64
pollableInputStreamReadNonblocking a
stream Maybe ByteString
buffer Maybe b
cancellable = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
let count :: Word64
count = case Maybe ByteString
buffer of
Maybe ByteString
Nothing -> Word64
0
Just ByteString
jBuffer -> Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
jBuffer
Ptr PollableInputStream
stream' <- a -> IO (Ptr PollableInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
Ptr Word8
maybeBuffer <- case Maybe ByteString
buffer of
Maybe ByteString
Nothing -> Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
forall a. Ptr a
nullPtr
Just ByteString
jBuffer -> do
Ptr Word8
jBuffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
jBuffer
Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
jBuffer'
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr PollableInputStream
-> Ptr Word8
-> Word64
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO Int64
g_pollable_input_stream_read_nonblocking Ptr PollableInputStream
stream' Ptr Word8
maybeBuffer Word64
count Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
) (do
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer
)
#if defined(ENABLE_OVERLOADING)
data PollableInputStreamReadNonblockingMethodInfo
instance (signature ~ (Maybe (ByteString) -> Maybe (b) -> m Int64), MonadIO m, IsPollableInputStream a, Gio.Cancellable.IsCancellable b) => O.MethodInfo PollableInputStreamReadNonblockingMethodInfo a signature where
overloadedMethod = pollableInputStreamReadNonblocking
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PollableInputStream = PollableInputStreamSignalList
type PollableInputStreamSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif