{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.SimpleIOStream
(
SimpleIOStream(..) ,
IsSimpleIOStream ,
toSimpleIOStream ,
noSimpleIOStream ,
#if defined(ENABLE_OVERLOADING)
ResolveSimpleIOStreamMethod ,
#endif
simpleIOStreamNew ,
#if defined(ENABLE_OVERLOADING)
SimpleIOStreamInputStreamPropertyInfo ,
#endif
constructSimpleIOStreamInputStream ,
getSimpleIOStreamInputStream ,
#if defined(ENABLE_OVERLOADING)
simpleIOStreamInputStream ,
#endif
#if defined(ENABLE_OVERLOADING)
SimpleIOStreamOutputStreamPropertyInfo ,
#endif
constructSimpleIOStreamOutputStream ,
getSimpleIOStreamOutputStream ,
#if defined(ENABLE_OVERLOADING)
simpleIOStreamOutputStream ,
#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 {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
newtype SimpleIOStream = SimpleIOStream (ManagedPtr SimpleIOStream)
deriving (SimpleIOStream -> SimpleIOStream -> Bool
(SimpleIOStream -> SimpleIOStream -> Bool)
-> (SimpleIOStream -> SimpleIOStream -> Bool) -> Eq SimpleIOStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleIOStream -> SimpleIOStream -> Bool
$c/= :: SimpleIOStream -> SimpleIOStream -> Bool
== :: SimpleIOStream -> SimpleIOStream -> Bool
$c== :: SimpleIOStream -> SimpleIOStream -> Bool
Eq)
foreign import ccall "g_simple_io_stream_get_type"
c_g_simple_io_stream_get_type :: IO GType
instance GObject SimpleIOStream where
gobjectType :: IO GType
gobjectType = IO GType
c_g_simple_io_stream_get_type
instance B.GValue.IsGValue SimpleIOStream where
toGValue :: SimpleIOStream -> IO GValue
toGValue o :: SimpleIOStream
o = do
GType
gtype <- IO GType
c_g_simple_io_stream_get_type
SimpleIOStream -> (Ptr SimpleIOStream -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SimpleIOStream
o (GType
-> (GValue -> Ptr SimpleIOStream -> IO ())
-> Ptr SimpleIOStream
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SimpleIOStream -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO SimpleIOStream
fromGValue gv :: GValue
gv = do
Ptr SimpleIOStream
ptr <- GValue -> IO (Ptr SimpleIOStream)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr SimpleIOStream)
(ManagedPtr SimpleIOStream -> SimpleIOStream)
-> Ptr SimpleIOStream -> IO SimpleIOStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SimpleIOStream -> SimpleIOStream
SimpleIOStream Ptr SimpleIOStream
ptr
class (GObject o, O.IsDescendantOf SimpleIOStream o) => IsSimpleIOStream o
instance (GObject o, O.IsDescendantOf SimpleIOStream o) => IsSimpleIOStream o
instance O.HasParentTypes SimpleIOStream
type instance O.ParentTypes SimpleIOStream = '[Gio.IOStream.IOStream, GObject.Object.Object]
toSimpleIOStream :: (MonadIO m, IsSimpleIOStream o) => o -> m SimpleIOStream
toSimpleIOStream :: o -> m SimpleIOStream
toSimpleIOStream = IO SimpleIOStream -> m SimpleIOStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SimpleIOStream -> m SimpleIOStream)
-> (o -> IO SimpleIOStream) -> o -> m SimpleIOStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SimpleIOStream -> SimpleIOStream)
-> o -> IO SimpleIOStream
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr SimpleIOStream -> SimpleIOStream
SimpleIOStream
noSimpleIOStream :: Maybe SimpleIOStream
noSimpleIOStream :: Maybe SimpleIOStream
noSimpleIOStream = Maybe SimpleIOStream
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveSimpleIOStreamMethod (t :: Symbol) (o :: *) :: * where
ResolveSimpleIOStreamMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSimpleIOStreamMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSimpleIOStreamMethod "clearPending" o = Gio.IOStream.IOStreamClearPendingMethodInfo
ResolveSimpleIOStreamMethod "close" o = Gio.IOStream.IOStreamCloseMethodInfo
ResolveSimpleIOStreamMethod "closeAsync" o = Gio.IOStream.IOStreamCloseAsyncMethodInfo
ResolveSimpleIOStreamMethod "closeFinish" o = Gio.IOStream.IOStreamCloseFinishMethodInfo
ResolveSimpleIOStreamMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSimpleIOStreamMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSimpleIOStreamMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSimpleIOStreamMethod "hasPending" o = Gio.IOStream.IOStreamHasPendingMethodInfo
ResolveSimpleIOStreamMethod "isClosed" o = Gio.IOStream.IOStreamIsClosedMethodInfo
ResolveSimpleIOStreamMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSimpleIOStreamMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSimpleIOStreamMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSimpleIOStreamMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSimpleIOStreamMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSimpleIOStreamMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSimpleIOStreamMethod "spliceAsync" o = Gio.IOStream.IOStreamSpliceAsyncMethodInfo
ResolveSimpleIOStreamMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSimpleIOStreamMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSimpleIOStreamMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSimpleIOStreamMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSimpleIOStreamMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSimpleIOStreamMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSimpleIOStreamMethod "getInputStream" o = Gio.IOStream.IOStreamGetInputStreamMethodInfo
ResolveSimpleIOStreamMethod "getOutputStream" o = Gio.IOStream.IOStreamGetOutputStreamMethodInfo
ResolveSimpleIOStreamMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSimpleIOStreamMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSimpleIOStreamMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSimpleIOStreamMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSimpleIOStreamMethod "setPending" o = Gio.IOStream.IOStreamSetPendingMethodInfo
ResolveSimpleIOStreamMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSimpleIOStreamMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSimpleIOStreamMethod t SimpleIOStream, O.MethodInfo info SimpleIOStream p) => OL.IsLabel t (SimpleIOStream -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getSimpleIOStreamInputStream :: (MonadIO m, IsSimpleIOStream o) => o -> m (Maybe Gio.InputStream.InputStream)
getSimpleIOStreamInputStream :: o -> m (Maybe InputStream)
getSimpleIOStreamInputStream obj :: o
obj = IO (Maybe InputStream) -> m (Maybe InputStream)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe InputStream) -> m (Maybe InputStream))
-> IO (Maybe InputStream) -> m (Maybe 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
constructSimpleIOStreamInputStream :: (IsSimpleIOStream o, Gio.InputStream.IsInputStream a) => a -> IO (GValueConstruct o)
constructSimpleIOStreamInputStream :: a -> IO (GValueConstruct o)
constructSimpleIOStreamInputStream val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "input-stream" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
#if defined(ENABLE_OVERLOADING)
data SimpleIOStreamInputStreamPropertyInfo
instance AttrInfo SimpleIOStreamInputStreamPropertyInfo where
type AttrAllowedOps SimpleIOStreamInputStreamPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SimpleIOStreamInputStreamPropertyInfo = IsSimpleIOStream
type AttrSetTypeConstraint SimpleIOStreamInputStreamPropertyInfo = Gio.InputStream.IsInputStream
type AttrTransferTypeConstraint SimpleIOStreamInputStreamPropertyInfo = Gio.InputStream.IsInputStream
type AttrTransferType SimpleIOStreamInputStreamPropertyInfo = Gio.InputStream.InputStream
type AttrGetType SimpleIOStreamInputStreamPropertyInfo = (Maybe Gio.InputStream.InputStream)
type AttrLabel SimpleIOStreamInputStreamPropertyInfo = "input-stream"
type AttrOrigin SimpleIOStreamInputStreamPropertyInfo = SimpleIOStream
attrGet = getSimpleIOStreamInputStream
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gio.InputStream.InputStream v
attrConstruct = constructSimpleIOStreamInputStream
attrClear = undefined
#endif
getSimpleIOStreamOutputStream :: (MonadIO m, IsSimpleIOStream o) => o -> m (Maybe Gio.OutputStream.OutputStream)
getSimpleIOStreamOutputStream :: o -> m (Maybe OutputStream)
getSimpleIOStreamOutputStream obj :: o
obj = IO (Maybe OutputStream) -> m (Maybe OutputStream)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe OutputStream) -> m (Maybe OutputStream))
-> IO (Maybe OutputStream) -> m (Maybe 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
constructSimpleIOStreamOutputStream :: (IsSimpleIOStream o, Gio.OutputStream.IsOutputStream a) => a -> IO (GValueConstruct o)
constructSimpleIOStreamOutputStream :: a -> IO (GValueConstruct o)
constructSimpleIOStreamOutputStream val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "output-stream" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
#if defined(ENABLE_OVERLOADING)
data SimpleIOStreamOutputStreamPropertyInfo
instance AttrInfo SimpleIOStreamOutputStreamPropertyInfo where
type AttrAllowedOps SimpleIOStreamOutputStreamPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SimpleIOStreamOutputStreamPropertyInfo = IsSimpleIOStream
type AttrSetTypeConstraint SimpleIOStreamOutputStreamPropertyInfo = Gio.OutputStream.IsOutputStream
type AttrTransferTypeConstraint SimpleIOStreamOutputStreamPropertyInfo = Gio.OutputStream.IsOutputStream
type AttrTransferType SimpleIOStreamOutputStreamPropertyInfo = Gio.OutputStream.OutputStream
type AttrGetType SimpleIOStreamOutputStreamPropertyInfo = (Maybe Gio.OutputStream.OutputStream)
type AttrLabel SimpleIOStreamOutputStreamPropertyInfo = "output-stream"
type AttrOrigin SimpleIOStreamOutputStreamPropertyInfo = SimpleIOStream
attrGet = getSimpleIOStreamOutputStream
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gio.OutputStream.OutputStream v
attrConstruct = constructSimpleIOStreamOutputStream
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SimpleIOStream
type instance O.AttributeList SimpleIOStream = SimpleIOStreamAttributeList
type SimpleIOStreamAttributeList = ('[ '("closed", Gio.IOStream.IOStreamClosedPropertyInfo), '("inputStream", SimpleIOStreamInputStreamPropertyInfo), '("outputStream", SimpleIOStreamOutputStreamPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
simpleIOStreamInputStream :: AttrLabelProxy "inputStream"
simpleIOStreamInputStream = AttrLabelProxy
simpleIOStreamOutputStream :: AttrLabelProxy "outputStream"
simpleIOStreamOutputStream = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SimpleIOStream = SimpleIOStreamSignalList
type SimpleIOStreamSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_simple_io_stream_new" g_simple_io_stream_new ::
Ptr Gio.InputStream.InputStream ->
Ptr Gio.OutputStream.OutputStream ->
IO (Ptr SimpleIOStream)
simpleIOStreamNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.InputStream.IsInputStream a, Gio.OutputStream.IsOutputStream b) =>
a
-> b
-> m SimpleIOStream
simpleIOStreamNew :: a -> b -> m SimpleIOStream
simpleIOStreamNew inputStream :: a
inputStream outputStream :: b
outputStream = IO SimpleIOStream -> m SimpleIOStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SimpleIOStream -> m SimpleIOStream)
-> IO SimpleIOStream -> m SimpleIOStream
forall a b. (a -> b) -> a -> b
$ do
Ptr InputStream
inputStream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
inputStream
Ptr OutputStream
outputStream' <- b -> IO (Ptr OutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
outputStream
Ptr SimpleIOStream
result <- Ptr InputStream -> Ptr OutputStream -> IO (Ptr SimpleIOStream)
g_simple_io_stream_new Ptr InputStream
inputStream' Ptr OutputStream
outputStream'
Text -> Ptr SimpleIOStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "simpleIOStreamNew" Ptr SimpleIOStream
result
SimpleIOStream
result' <- ((ManagedPtr SimpleIOStream -> SimpleIOStream)
-> Ptr SimpleIOStream -> IO SimpleIOStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SimpleIOStream -> SimpleIOStream
SimpleIOStream) Ptr SimpleIOStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
inputStream
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
outputStream
SimpleIOStream -> IO SimpleIOStream
forall (m :: * -> *) a. Monad m => a -> m a
return SimpleIOStream
result'
#if defined(ENABLE_OVERLOADING)
#endif