{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.TcpWrapperConnection
(
TcpWrapperConnection(..) ,
IsTcpWrapperConnection ,
toTcpWrapperConnection ,
#if defined(ENABLE_OVERLOADING)
ResolveTcpWrapperConnectionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TcpWrapperConnectionGetBaseIoStreamMethodInfo,
#endif
tcpWrapperConnectionGetBaseIoStream ,
tcpWrapperConnectionNew ,
#if defined(ENABLE_OVERLOADING)
TcpWrapperConnectionBaseIoStreamPropertyInfo,
#endif
constructTcpWrapperConnectionBaseIoStream,
getTcpWrapperConnectionBaseIoStream ,
#if defined(ENABLE_OVERLOADING)
tcpWrapperConnectionBaseIoStream ,
#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.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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.Socket as Gio.Socket
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketConnection as Gio.SocketConnection
import {-# SOURCE #-} qualified GI.Gio.Objects.TcpConnection as Gio.TcpConnection
newtype TcpWrapperConnection = TcpWrapperConnection (SP.ManagedPtr TcpWrapperConnection)
deriving (TcpWrapperConnection -> TcpWrapperConnection -> Bool
(TcpWrapperConnection -> TcpWrapperConnection -> Bool)
-> (TcpWrapperConnection -> TcpWrapperConnection -> Bool)
-> Eq TcpWrapperConnection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TcpWrapperConnection -> TcpWrapperConnection -> Bool
$c/= :: TcpWrapperConnection -> TcpWrapperConnection -> Bool
== :: TcpWrapperConnection -> TcpWrapperConnection -> Bool
$c== :: TcpWrapperConnection -> TcpWrapperConnection -> Bool
Eq)
instance SP.ManagedPtrNewtype TcpWrapperConnection where
toManagedPtr :: TcpWrapperConnection -> ManagedPtr TcpWrapperConnection
toManagedPtr (TcpWrapperConnection ManagedPtr TcpWrapperConnection
p) = ManagedPtr TcpWrapperConnection
p
foreign import ccall "g_tcp_wrapper_connection_get_type"
c_g_tcp_wrapper_connection_get_type :: IO B.Types.GType
instance B.Types.TypedObject TcpWrapperConnection where
glibType :: IO GType
glibType = IO GType
c_g_tcp_wrapper_connection_get_type
instance B.Types.GObject TcpWrapperConnection
instance B.GValue.IsGValue TcpWrapperConnection where
toGValue :: TcpWrapperConnection -> IO GValue
toGValue TcpWrapperConnection
o = do
GType
gtype <- IO GType
c_g_tcp_wrapper_connection_get_type
TcpWrapperConnection
-> (Ptr TcpWrapperConnection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TcpWrapperConnection
o (GType
-> (GValue -> Ptr TcpWrapperConnection -> IO ())
-> Ptr TcpWrapperConnection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TcpWrapperConnection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO TcpWrapperConnection
fromGValue GValue
gv = do
Ptr TcpWrapperConnection
ptr <- GValue -> IO (Ptr TcpWrapperConnection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TcpWrapperConnection)
(ManagedPtr TcpWrapperConnection -> TcpWrapperConnection)
-> Ptr TcpWrapperConnection -> IO TcpWrapperConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TcpWrapperConnection -> TcpWrapperConnection
TcpWrapperConnection Ptr TcpWrapperConnection
ptr
class (SP.GObject o, O.IsDescendantOf TcpWrapperConnection o) => IsTcpWrapperConnection o
instance (SP.GObject o, O.IsDescendantOf TcpWrapperConnection o) => IsTcpWrapperConnection o
instance O.HasParentTypes TcpWrapperConnection
type instance O.ParentTypes TcpWrapperConnection = '[Gio.TcpConnection.TcpConnection, Gio.SocketConnection.SocketConnection, Gio.IOStream.IOStream, GObject.Object.Object]
toTcpWrapperConnection :: (MonadIO m, IsTcpWrapperConnection o) => o -> m TcpWrapperConnection
toTcpWrapperConnection :: o -> m TcpWrapperConnection
toTcpWrapperConnection = IO TcpWrapperConnection -> m TcpWrapperConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TcpWrapperConnection -> m TcpWrapperConnection)
-> (o -> IO TcpWrapperConnection) -> o -> m TcpWrapperConnection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TcpWrapperConnection -> TcpWrapperConnection)
-> o -> IO TcpWrapperConnection
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TcpWrapperConnection -> TcpWrapperConnection
TcpWrapperConnection
#if defined(ENABLE_OVERLOADING)
type family ResolveTcpWrapperConnectionMethod (t :: Symbol) (o :: *) :: * where
ResolveTcpWrapperConnectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTcpWrapperConnectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTcpWrapperConnectionMethod "clearPending" o = Gio.IOStream.IOStreamClearPendingMethodInfo
ResolveTcpWrapperConnectionMethod "close" o = Gio.IOStream.IOStreamCloseMethodInfo
ResolveTcpWrapperConnectionMethod "closeAsync" o = Gio.IOStream.IOStreamCloseAsyncMethodInfo
ResolveTcpWrapperConnectionMethod "closeFinish" o = Gio.IOStream.IOStreamCloseFinishMethodInfo
ResolveTcpWrapperConnectionMethod "connect" o = Gio.SocketConnection.SocketConnectionConnectMethodInfo
ResolveTcpWrapperConnectionMethod "connectAsync" o = Gio.SocketConnection.SocketConnectionConnectAsyncMethodInfo
ResolveTcpWrapperConnectionMethod "connectFinish" o = Gio.SocketConnection.SocketConnectionConnectFinishMethodInfo
ResolveTcpWrapperConnectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTcpWrapperConnectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTcpWrapperConnectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTcpWrapperConnectionMethod "hasPending" o = Gio.IOStream.IOStreamHasPendingMethodInfo
ResolveTcpWrapperConnectionMethod "isClosed" o = Gio.IOStream.IOStreamIsClosedMethodInfo
ResolveTcpWrapperConnectionMethod "isConnected" o = Gio.SocketConnection.SocketConnectionIsConnectedMethodInfo
ResolveTcpWrapperConnectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTcpWrapperConnectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTcpWrapperConnectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTcpWrapperConnectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTcpWrapperConnectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTcpWrapperConnectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTcpWrapperConnectionMethod "spliceAsync" o = Gio.IOStream.IOStreamSpliceAsyncMethodInfo
ResolveTcpWrapperConnectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTcpWrapperConnectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTcpWrapperConnectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTcpWrapperConnectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTcpWrapperConnectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTcpWrapperConnectionMethod "getBaseIoStream" o = TcpWrapperConnectionGetBaseIoStreamMethodInfo
ResolveTcpWrapperConnectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTcpWrapperConnectionMethod "getGracefulDisconnect" o = Gio.TcpConnection.TcpConnectionGetGracefulDisconnectMethodInfo
ResolveTcpWrapperConnectionMethod "getInputStream" o = Gio.IOStream.IOStreamGetInputStreamMethodInfo
ResolveTcpWrapperConnectionMethod "getLocalAddress" o = Gio.SocketConnection.SocketConnectionGetLocalAddressMethodInfo
ResolveTcpWrapperConnectionMethod "getOutputStream" o = Gio.IOStream.IOStreamGetOutputStreamMethodInfo
ResolveTcpWrapperConnectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTcpWrapperConnectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTcpWrapperConnectionMethod "getRemoteAddress" o = Gio.SocketConnection.SocketConnectionGetRemoteAddressMethodInfo
ResolveTcpWrapperConnectionMethod "getSocket" o = Gio.SocketConnection.SocketConnectionGetSocketMethodInfo
ResolveTcpWrapperConnectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTcpWrapperConnectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTcpWrapperConnectionMethod "setGracefulDisconnect" o = Gio.TcpConnection.TcpConnectionSetGracefulDisconnectMethodInfo
ResolveTcpWrapperConnectionMethod "setPending" o = Gio.IOStream.IOStreamSetPendingMethodInfo
ResolveTcpWrapperConnectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTcpWrapperConnectionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTcpWrapperConnectionMethod t TcpWrapperConnection, O.MethodInfo info TcpWrapperConnection p) => OL.IsLabel t (TcpWrapperConnection -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getTcpWrapperConnectionBaseIoStream :: (MonadIO m, IsTcpWrapperConnection o) => o -> m Gio.IOStream.IOStream
getTcpWrapperConnectionBaseIoStream :: o -> m IOStream
getTcpWrapperConnectionBaseIoStream o
obj = IO IOStream -> m IOStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOStream -> m IOStream) -> IO IOStream -> m IOStream
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe IOStream) -> IO IOStream
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTcpWrapperConnectionBaseIoStream" (IO (Maybe IOStream) -> IO IOStream)
-> IO (Maybe IOStream) -> IO IOStream
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr IOStream -> IOStream)
-> IO (Maybe IOStream)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"base-io-stream" ManagedPtr IOStream -> IOStream
Gio.IOStream.IOStream
constructTcpWrapperConnectionBaseIoStream :: (IsTcpWrapperConnection o, MIO.MonadIO m, Gio.IOStream.IsIOStream a) => a -> m (GValueConstruct o)
constructTcpWrapperConnectionBaseIoStream :: a -> m (GValueConstruct o)
constructTcpWrapperConnectionBaseIoStream a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"base-io-stream" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data TcpWrapperConnectionBaseIoStreamPropertyInfo
instance AttrInfo TcpWrapperConnectionBaseIoStreamPropertyInfo where
type AttrAllowedOps TcpWrapperConnectionBaseIoStreamPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint TcpWrapperConnectionBaseIoStreamPropertyInfo = IsTcpWrapperConnection
type AttrSetTypeConstraint TcpWrapperConnectionBaseIoStreamPropertyInfo = Gio.IOStream.IsIOStream
type AttrTransferTypeConstraint TcpWrapperConnectionBaseIoStreamPropertyInfo = Gio.IOStream.IsIOStream
type AttrTransferType TcpWrapperConnectionBaseIoStreamPropertyInfo = Gio.IOStream.IOStream
type AttrGetType TcpWrapperConnectionBaseIoStreamPropertyInfo = Gio.IOStream.IOStream
type AttrLabel TcpWrapperConnectionBaseIoStreamPropertyInfo = "base-io-stream"
type AttrOrigin TcpWrapperConnectionBaseIoStreamPropertyInfo = TcpWrapperConnection
attrGet = getTcpWrapperConnectionBaseIoStream
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gio.IOStream.IOStream v
attrConstruct = constructTcpWrapperConnectionBaseIoStream
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TcpWrapperConnection
type instance O.AttributeList TcpWrapperConnection = TcpWrapperConnectionAttributeList
type TcpWrapperConnectionAttributeList = ('[ '("baseIoStream", TcpWrapperConnectionBaseIoStreamPropertyInfo), '("closed", Gio.IOStream.IOStreamClosedPropertyInfo), '("gracefulDisconnect", Gio.TcpConnection.TcpConnectionGracefulDisconnectPropertyInfo), '("inputStream", Gio.IOStream.IOStreamInputStreamPropertyInfo), '("outputStream", Gio.IOStream.IOStreamOutputStreamPropertyInfo), '("socket", Gio.SocketConnection.SocketConnectionSocketPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
tcpWrapperConnectionBaseIoStream :: AttrLabelProxy "baseIoStream"
tcpWrapperConnectionBaseIoStream = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TcpWrapperConnection = TcpWrapperConnectionSignalList
type TcpWrapperConnectionSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_tcp_wrapper_connection_new" g_tcp_wrapper_connection_new ::
Ptr Gio.IOStream.IOStream ->
Ptr Gio.Socket.Socket ->
IO (Ptr TcpWrapperConnection)
tcpWrapperConnectionNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.IOStream.IsIOStream a, Gio.Socket.IsSocket b) =>
a
-> b
-> m TcpWrapperConnection
tcpWrapperConnectionNew :: a -> b -> m TcpWrapperConnection
tcpWrapperConnectionNew a
baseIoStream b
socket = IO TcpWrapperConnection -> m TcpWrapperConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TcpWrapperConnection -> m TcpWrapperConnection)
-> IO TcpWrapperConnection -> m TcpWrapperConnection
forall a b. (a -> b) -> a -> b
$ do
Ptr IOStream
baseIoStream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
baseIoStream
Ptr Socket
socket' <- b -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
socket
Ptr TcpWrapperConnection
result <- Ptr IOStream -> Ptr Socket -> IO (Ptr TcpWrapperConnection)
g_tcp_wrapper_connection_new Ptr IOStream
baseIoStream' Ptr Socket
socket'
Text -> Ptr TcpWrapperConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tcpWrapperConnectionNew" Ptr TcpWrapperConnection
result
TcpWrapperConnection
result' <- ((ManagedPtr TcpWrapperConnection -> TcpWrapperConnection)
-> Ptr TcpWrapperConnection -> IO TcpWrapperConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TcpWrapperConnection -> TcpWrapperConnection
TcpWrapperConnection) Ptr TcpWrapperConnection
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
baseIoStream
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
socket
TcpWrapperConnection -> IO TcpWrapperConnection
forall (m :: * -> *) a. Monad m => a -> m a
return TcpWrapperConnection
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_tcp_wrapper_connection_get_base_io_stream" g_tcp_wrapper_connection_get_base_io_stream ::
Ptr TcpWrapperConnection ->
IO (Ptr Gio.IOStream.IOStream)
tcpWrapperConnectionGetBaseIoStream ::
(B.CallStack.HasCallStack, MonadIO m, IsTcpWrapperConnection a) =>
a
-> m Gio.IOStream.IOStream
tcpWrapperConnectionGetBaseIoStream :: a -> m IOStream
tcpWrapperConnectionGetBaseIoStream a
conn = IO IOStream -> m IOStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOStream -> m IOStream) -> IO IOStream -> m IOStream
forall a b. (a -> b) -> a -> b
$ do
Ptr TcpWrapperConnection
conn' <- a -> IO (Ptr TcpWrapperConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr IOStream
result <- Ptr TcpWrapperConnection -> IO (Ptr IOStream)
g_tcp_wrapper_connection_get_base_io_stream Ptr TcpWrapperConnection
conn'
Text -> Ptr IOStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tcpWrapperConnectionGetBaseIoStream" Ptr IOStream
result
IOStream
result' <- ((ManagedPtr IOStream -> IOStream) -> Ptr IOStream -> IO IOStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr IOStream -> IOStream
Gio.IOStream.IOStream) Ptr IOStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
IOStream -> IO IOStream
forall (m :: * -> *) a. Monad m => a -> m a
return IOStream
result'
#if defined(ENABLE_OVERLOADING)
data TcpWrapperConnectionGetBaseIoStreamMethodInfo
instance (signature ~ (m Gio.IOStream.IOStream), MonadIO m, IsTcpWrapperConnection a) => O.MethodInfo TcpWrapperConnectionGetBaseIoStreamMethodInfo a signature where
overloadedMethod = tcpWrapperConnectionGetBaseIoStream
#endif