{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.TlsClientConnection
(
TlsClientConnection(..) ,
IsTlsClientConnection ,
toTlsClientConnection ,
#if defined(ENABLE_OVERLOADING)
ResolveTlsClientConnectionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionCopySessionStateMethodInfo,
#endif
tlsClientConnectionCopySessionState ,
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionGetAcceptedCasMethodInfo,
#endif
tlsClientConnectionGetAcceptedCas ,
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionGetServerIdentityMethodInfo,
#endif
tlsClientConnectionGetServerIdentity ,
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionGetUseSsl3MethodInfo ,
#endif
tlsClientConnectionGetUseSsl3 ,
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionGetValidationFlagsMethodInfo,
#endif
tlsClientConnectionGetValidationFlags ,
tlsClientConnectionNew ,
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionSetServerIdentityMethodInfo,
#endif
tlsClientConnectionSetServerIdentity ,
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionSetUseSsl3MethodInfo ,
#endif
tlsClientConnectionSetUseSsl3 ,
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionSetValidationFlagsMethodInfo,
#endif
tlsClientConnectionSetValidationFlags ,
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionAcceptedCasPropertyInfo,
#endif
getTlsClientConnectionAcceptedCas ,
#if defined(ENABLE_OVERLOADING)
tlsClientConnectionAcceptedCas ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionServerIdentityPropertyInfo,
#endif
constructTlsClientConnectionServerIdentity,
getTlsClientConnectionServerIdentity ,
setTlsClientConnectionServerIdentity ,
#if defined(ENABLE_OVERLOADING)
tlsClientConnectionServerIdentity ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionUseSsl3PropertyInfo ,
#endif
constructTlsClientConnectionUseSsl3 ,
getTlsClientConnectionUseSsl3 ,
setTlsClientConnectionUseSsl3 ,
#if defined(ENABLE_OVERLOADING)
tlsClientConnectionUseSsl3 ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsClientConnectionValidationFlagsPropertyInfo,
#endif
constructTlsClientConnectionValidationFlags,
getTlsClientConnectionValidationFlags ,
setTlsClientConnectionValidationFlags ,
#if defined(ENABLE_OVERLOADING)
tlsClientConnectionValidationFlags ,
#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.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsConnection as Gio.TlsConnection
newtype TlsClientConnection = TlsClientConnection (SP.ManagedPtr TlsClientConnection)
deriving (TlsClientConnection -> TlsClientConnection -> Bool
(TlsClientConnection -> TlsClientConnection -> Bool)
-> (TlsClientConnection -> TlsClientConnection -> Bool)
-> Eq TlsClientConnection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsClientConnection -> TlsClientConnection -> Bool
$c/= :: TlsClientConnection -> TlsClientConnection -> Bool
== :: TlsClientConnection -> TlsClientConnection -> Bool
$c== :: TlsClientConnection -> TlsClientConnection -> Bool
Eq)
instance SP.ManagedPtrNewtype TlsClientConnection where
toManagedPtr :: TlsClientConnection -> ManagedPtr TlsClientConnection
toManagedPtr (TlsClientConnection ManagedPtr TlsClientConnection
p) = ManagedPtr TlsClientConnection
p
foreign import ccall "g_tls_client_connection_get_type"
c_g_tls_client_connection_get_type :: IO B.Types.GType
instance B.Types.TypedObject TlsClientConnection where
glibType :: IO GType
glibType = IO GType
c_g_tls_client_connection_get_type
instance B.Types.GObject TlsClientConnection
instance B.GValue.IsGValue TlsClientConnection where
toGValue :: TlsClientConnection -> IO GValue
toGValue TlsClientConnection
o = do
GType
gtype <- IO GType
c_g_tls_client_connection_get_type
TlsClientConnection
-> (Ptr TlsClientConnection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsClientConnection
o (GType
-> (GValue -> Ptr TlsClientConnection -> IO ())
-> Ptr TlsClientConnection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TlsClientConnection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO TlsClientConnection
fromGValue GValue
gv = do
Ptr TlsClientConnection
ptr <- GValue -> IO (Ptr TlsClientConnection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TlsClientConnection)
(ManagedPtr TlsClientConnection -> TlsClientConnection)
-> Ptr TlsClientConnection -> IO TlsClientConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TlsClientConnection -> TlsClientConnection
TlsClientConnection Ptr TlsClientConnection
ptr
class (SP.GObject o, O.IsDescendantOf TlsClientConnection o) => IsTlsClientConnection o
instance (SP.GObject o, O.IsDescendantOf TlsClientConnection o) => IsTlsClientConnection o
instance O.HasParentTypes TlsClientConnection
type instance O.ParentTypes TlsClientConnection = '[GObject.Object.Object, Gio.TlsConnection.TlsConnection, Gio.IOStream.IOStream]
toTlsClientConnection :: (MonadIO m, IsTlsClientConnection o) => o -> m TlsClientConnection
toTlsClientConnection :: o -> m TlsClientConnection
toTlsClientConnection = IO TlsClientConnection -> m TlsClientConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsClientConnection -> m TlsClientConnection)
-> (o -> IO TlsClientConnection) -> o -> m TlsClientConnection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TlsClientConnection -> TlsClientConnection)
-> o -> IO TlsClientConnection
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TlsClientConnection -> TlsClientConnection
TlsClientConnection
getTlsClientConnectionAcceptedCas :: (MonadIO m, IsTlsClientConnection o) => o -> m ([Ptr ()])
getTlsClientConnectionAcceptedCas :: o -> m [Ptr ()]
getTlsClientConnectionAcceptedCas o
obj = IO [Ptr ()] -> m [Ptr ()]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Ptr ()] -> m [Ptr ()]) -> IO [Ptr ()] -> m [Ptr ()]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [Ptr ()]
forall a b. GObject a => a -> String -> IO [Ptr b]
B.Properties.getObjectPropertyPtrGList o
obj String
"accepted-cas"
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionAcceptedCasPropertyInfo
instance AttrInfo TlsClientConnectionAcceptedCasPropertyInfo where
type AttrAllowedOps TlsClientConnectionAcceptedCasPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint TlsClientConnectionAcceptedCasPropertyInfo = IsTlsClientConnection
type AttrSetTypeConstraint TlsClientConnectionAcceptedCasPropertyInfo = (~) ()
type AttrTransferTypeConstraint TlsClientConnectionAcceptedCasPropertyInfo = (~) ()
type AttrTransferType TlsClientConnectionAcceptedCasPropertyInfo = ()
type AttrGetType TlsClientConnectionAcceptedCasPropertyInfo = ([Ptr ()])
type AttrLabel TlsClientConnectionAcceptedCasPropertyInfo = "accepted-cas"
type AttrOrigin TlsClientConnectionAcceptedCasPropertyInfo = TlsClientConnection
attrGet = getTlsClientConnectionAcceptedCas
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getTlsClientConnectionServerIdentity :: (MonadIO m, IsTlsClientConnection o) => o -> m Gio.SocketConnectable.SocketConnectable
getTlsClientConnectionServerIdentity :: o -> m SocketConnectable
getTlsClientConnectionServerIdentity o
obj = IO SocketConnectable -> m SocketConnectable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketConnectable -> m SocketConnectable)
-> IO SocketConnectable -> m SocketConnectable
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe SocketConnectable) -> IO SocketConnectable
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTlsClientConnectionServerIdentity" (IO (Maybe SocketConnectable) -> IO SocketConnectable)
-> IO (Maybe SocketConnectable) -> IO SocketConnectable
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr SocketConnectable -> SocketConnectable)
-> IO (Maybe SocketConnectable)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"server-identity" ManagedPtr SocketConnectable -> SocketConnectable
Gio.SocketConnectable.SocketConnectable
setTlsClientConnectionServerIdentity :: (MonadIO m, IsTlsClientConnection o, Gio.SocketConnectable.IsSocketConnectable a) => o -> a -> m ()
setTlsClientConnectionServerIdentity :: o -> a -> m ()
setTlsClientConnectionServerIdentity o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"server-identity" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTlsClientConnectionServerIdentity :: (IsTlsClientConnection o, MIO.MonadIO m, Gio.SocketConnectable.IsSocketConnectable a) => a -> m (GValueConstruct o)
constructTlsClientConnectionServerIdentity :: a -> m (GValueConstruct o)
constructTlsClientConnectionServerIdentity 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
"server-identity" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionServerIdentityPropertyInfo
instance AttrInfo TlsClientConnectionServerIdentityPropertyInfo where
type AttrAllowedOps TlsClientConnectionServerIdentityPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsClientConnectionServerIdentityPropertyInfo = IsTlsClientConnection
type AttrSetTypeConstraint TlsClientConnectionServerIdentityPropertyInfo = Gio.SocketConnectable.IsSocketConnectable
type AttrTransferTypeConstraint TlsClientConnectionServerIdentityPropertyInfo = Gio.SocketConnectable.IsSocketConnectable
type AttrTransferType TlsClientConnectionServerIdentityPropertyInfo = Gio.SocketConnectable.SocketConnectable
type AttrGetType TlsClientConnectionServerIdentityPropertyInfo = Gio.SocketConnectable.SocketConnectable
type AttrLabel TlsClientConnectionServerIdentityPropertyInfo = "server-identity"
type AttrOrigin TlsClientConnectionServerIdentityPropertyInfo = TlsClientConnection
attrGet = getTlsClientConnectionServerIdentity
attrSet = setTlsClientConnectionServerIdentity
attrTransfer _ v = do
unsafeCastTo Gio.SocketConnectable.SocketConnectable v
attrConstruct = constructTlsClientConnectionServerIdentity
attrClear = undefined
#endif
getTlsClientConnectionUseSsl3 :: (MonadIO m, IsTlsClientConnection o) => o -> m Bool
getTlsClientConnectionUseSsl3 :: o -> m Bool
getTlsClientConnectionUseSsl3 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 String
"use-ssl3"
setTlsClientConnectionUseSsl3 :: (MonadIO m, IsTlsClientConnection o) => o -> Bool -> m ()
setTlsClientConnectionUseSsl3 :: o -> Bool -> m ()
setTlsClientConnectionUseSsl3 o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-ssl3" Bool
val
constructTlsClientConnectionUseSsl3 :: (IsTlsClientConnection o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTlsClientConnectionUseSsl3 :: Bool -> m (GValueConstruct o)
constructTlsClientConnectionUseSsl3 Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-ssl3" Bool
val
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionUseSsl3PropertyInfo
instance AttrInfo TlsClientConnectionUseSsl3PropertyInfo where
type AttrAllowedOps TlsClientConnectionUseSsl3PropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsClientConnectionUseSsl3PropertyInfo = IsTlsClientConnection
type AttrSetTypeConstraint TlsClientConnectionUseSsl3PropertyInfo = (~) Bool
type AttrTransferTypeConstraint TlsClientConnectionUseSsl3PropertyInfo = (~) Bool
type AttrTransferType TlsClientConnectionUseSsl3PropertyInfo = Bool
type AttrGetType TlsClientConnectionUseSsl3PropertyInfo = Bool
type AttrLabel TlsClientConnectionUseSsl3PropertyInfo = "use-ssl3"
type AttrOrigin TlsClientConnectionUseSsl3PropertyInfo = TlsClientConnection
attrGet = getTlsClientConnectionUseSsl3
attrSet = setTlsClientConnectionUseSsl3
attrTransfer _ v = do
return v
attrConstruct = constructTlsClientConnectionUseSsl3
attrClear = undefined
#endif
getTlsClientConnectionValidationFlags :: (MonadIO m, IsTlsClientConnection o) => o -> m [Gio.Flags.TlsCertificateFlags]
getTlsClientConnectionValidationFlags :: o -> m [TlsCertificateFlags]
getTlsClientConnectionValidationFlags o
obj = IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TlsCertificateFlags] -> m [TlsCertificateFlags])
-> IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [TlsCertificateFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"validation-flags"
setTlsClientConnectionValidationFlags :: (MonadIO m, IsTlsClientConnection o) => o -> [Gio.Flags.TlsCertificateFlags] -> m ()
setTlsClientConnectionValidationFlags :: o -> [TlsCertificateFlags] -> m ()
setTlsClientConnectionValidationFlags o
obj [TlsCertificateFlags]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> [TlsCertificateFlags] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"validation-flags" [TlsCertificateFlags]
val
constructTlsClientConnectionValidationFlags :: (IsTlsClientConnection o, MIO.MonadIO m) => [Gio.Flags.TlsCertificateFlags] -> m (GValueConstruct o)
constructTlsClientConnectionValidationFlags :: [TlsCertificateFlags] -> m (GValueConstruct o)
constructTlsClientConnectionValidationFlags [TlsCertificateFlags]
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 -> [TlsCertificateFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"validation-flags" [TlsCertificateFlags]
val
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionValidationFlagsPropertyInfo
instance AttrInfo TlsClientConnectionValidationFlagsPropertyInfo where
type AttrAllowedOps TlsClientConnectionValidationFlagsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsClientConnectionValidationFlagsPropertyInfo = IsTlsClientConnection
type AttrSetTypeConstraint TlsClientConnectionValidationFlagsPropertyInfo = (~) [Gio.Flags.TlsCertificateFlags]
type AttrTransferTypeConstraint TlsClientConnectionValidationFlagsPropertyInfo = (~) [Gio.Flags.TlsCertificateFlags]
type AttrTransferType TlsClientConnectionValidationFlagsPropertyInfo = [Gio.Flags.TlsCertificateFlags]
type AttrGetType TlsClientConnectionValidationFlagsPropertyInfo = [Gio.Flags.TlsCertificateFlags]
type AttrLabel TlsClientConnectionValidationFlagsPropertyInfo = "validation-flags"
type AttrOrigin TlsClientConnectionValidationFlagsPropertyInfo = TlsClientConnection
attrGet = getTlsClientConnectionValidationFlags
attrSet = setTlsClientConnectionValidationFlags
attrTransfer _ v = do
return v
attrConstruct = constructTlsClientConnectionValidationFlags
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsClientConnection
type instance O.AttributeList TlsClientConnection = TlsClientConnectionAttributeList
type TlsClientConnectionAttributeList = ('[ '("acceptedCas", TlsClientConnectionAcceptedCasPropertyInfo), '("advertisedProtocols", Gio.TlsConnection.TlsConnectionAdvertisedProtocolsPropertyInfo), '("baseIoStream", Gio.TlsConnection.TlsConnectionBaseIoStreamPropertyInfo), '("certificate", Gio.TlsConnection.TlsConnectionCertificatePropertyInfo), '("closed", Gio.IOStream.IOStreamClosedPropertyInfo), '("database", Gio.TlsConnection.TlsConnectionDatabasePropertyInfo), '("inputStream", Gio.IOStream.IOStreamInputStreamPropertyInfo), '("interaction", Gio.TlsConnection.TlsConnectionInteractionPropertyInfo), '("negotiatedProtocol", Gio.TlsConnection.TlsConnectionNegotiatedProtocolPropertyInfo), '("outputStream", Gio.IOStream.IOStreamOutputStreamPropertyInfo), '("peerCertificate", Gio.TlsConnection.TlsConnectionPeerCertificatePropertyInfo), '("peerCertificateErrors", Gio.TlsConnection.TlsConnectionPeerCertificateErrorsPropertyInfo), '("rehandshakeMode", Gio.TlsConnection.TlsConnectionRehandshakeModePropertyInfo), '("requireCloseNotify", Gio.TlsConnection.TlsConnectionRequireCloseNotifyPropertyInfo), '("serverIdentity", TlsClientConnectionServerIdentityPropertyInfo), '("useSsl3", TlsClientConnectionUseSsl3PropertyInfo), '("useSystemCertdb", Gio.TlsConnection.TlsConnectionUseSystemCertdbPropertyInfo), '("validationFlags", TlsClientConnectionValidationFlagsPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
tlsClientConnectionAcceptedCas :: AttrLabelProxy "acceptedCas"
tlsClientConnectionAcceptedCas = AttrLabelProxy
tlsClientConnectionServerIdentity :: AttrLabelProxy "serverIdentity"
tlsClientConnectionServerIdentity = AttrLabelProxy
tlsClientConnectionUseSsl3 :: AttrLabelProxy "useSsl3"
tlsClientConnectionUseSsl3 = AttrLabelProxy
tlsClientConnectionValidationFlags :: AttrLabelProxy "validationFlags"
tlsClientConnectionValidationFlags = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveTlsClientConnectionMethod (t :: Symbol) (o :: *) :: * where
ResolveTlsClientConnectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTlsClientConnectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTlsClientConnectionMethod "clearPending" o = Gio.IOStream.IOStreamClearPendingMethodInfo
ResolveTlsClientConnectionMethod "close" o = Gio.IOStream.IOStreamCloseMethodInfo
ResolveTlsClientConnectionMethod "closeAsync" o = Gio.IOStream.IOStreamCloseAsyncMethodInfo
ResolveTlsClientConnectionMethod "closeFinish" o = Gio.IOStream.IOStreamCloseFinishMethodInfo
ResolveTlsClientConnectionMethod "copySessionState" o = TlsClientConnectionCopySessionStateMethodInfo
ResolveTlsClientConnectionMethod "emitAcceptCertificate" o = Gio.TlsConnection.TlsConnectionEmitAcceptCertificateMethodInfo
ResolveTlsClientConnectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTlsClientConnectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTlsClientConnectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTlsClientConnectionMethod "handshake" o = Gio.TlsConnection.TlsConnectionHandshakeMethodInfo
ResolveTlsClientConnectionMethod "handshakeAsync" o = Gio.TlsConnection.TlsConnectionHandshakeAsyncMethodInfo
ResolveTlsClientConnectionMethod "handshakeFinish" o = Gio.TlsConnection.TlsConnectionHandshakeFinishMethodInfo
ResolveTlsClientConnectionMethod "hasPending" o = Gio.IOStream.IOStreamHasPendingMethodInfo
ResolveTlsClientConnectionMethod "isClosed" o = Gio.IOStream.IOStreamIsClosedMethodInfo
ResolveTlsClientConnectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTlsClientConnectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTlsClientConnectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTlsClientConnectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTlsClientConnectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTlsClientConnectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTlsClientConnectionMethod "spliceAsync" o = Gio.IOStream.IOStreamSpliceAsyncMethodInfo
ResolveTlsClientConnectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTlsClientConnectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTlsClientConnectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTlsClientConnectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTlsClientConnectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTlsClientConnectionMethod "getAcceptedCas" o = TlsClientConnectionGetAcceptedCasMethodInfo
ResolveTlsClientConnectionMethod "getCertificate" o = Gio.TlsConnection.TlsConnectionGetCertificateMethodInfo
ResolveTlsClientConnectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTlsClientConnectionMethod "getDatabase" o = Gio.TlsConnection.TlsConnectionGetDatabaseMethodInfo
ResolveTlsClientConnectionMethod "getInputStream" o = Gio.IOStream.IOStreamGetInputStreamMethodInfo
ResolveTlsClientConnectionMethod "getInteraction" o = Gio.TlsConnection.TlsConnectionGetInteractionMethodInfo
ResolveTlsClientConnectionMethod "getNegotiatedProtocol" o = Gio.TlsConnection.TlsConnectionGetNegotiatedProtocolMethodInfo
ResolveTlsClientConnectionMethod "getOutputStream" o = Gio.IOStream.IOStreamGetOutputStreamMethodInfo
ResolveTlsClientConnectionMethod "getPeerCertificate" o = Gio.TlsConnection.TlsConnectionGetPeerCertificateMethodInfo
ResolveTlsClientConnectionMethod "getPeerCertificateErrors" o = Gio.TlsConnection.TlsConnectionGetPeerCertificateErrorsMethodInfo
ResolveTlsClientConnectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTlsClientConnectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTlsClientConnectionMethod "getRehandshakeMode" o = Gio.TlsConnection.TlsConnectionGetRehandshakeModeMethodInfo
ResolveTlsClientConnectionMethod "getRequireCloseNotify" o = Gio.TlsConnection.TlsConnectionGetRequireCloseNotifyMethodInfo
ResolveTlsClientConnectionMethod "getServerIdentity" o = TlsClientConnectionGetServerIdentityMethodInfo
ResolveTlsClientConnectionMethod "getUseSsl3" o = TlsClientConnectionGetUseSsl3MethodInfo
ResolveTlsClientConnectionMethod "getUseSystemCertdb" o = Gio.TlsConnection.TlsConnectionGetUseSystemCertdbMethodInfo
ResolveTlsClientConnectionMethod "getValidationFlags" o = TlsClientConnectionGetValidationFlagsMethodInfo
ResolveTlsClientConnectionMethod "setAdvertisedProtocols" o = Gio.TlsConnection.TlsConnectionSetAdvertisedProtocolsMethodInfo
ResolveTlsClientConnectionMethod "setCertificate" o = Gio.TlsConnection.TlsConnectionSetCertificateMethodInfo
ResolveTlsClientConnectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTlsClientConnectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTlsClientConnectionMethod "setDatabase" o = Gio.TlsConnection.TlsConnectionSetDatabaseMethodInfo
ResolveTlsClientConnectionMethod "setInteraction" o = Gio.TlsConnection.TlsConnectionSetInteractionMethodInfo
ResolveTlsClientConnectionMethod "setPending" o = Gio.IOStream.IOStreamSetPendingMethodInfo
ResolveTlsClientConnectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTlsClientConnectionMethod "setRehandshakeMode" o = Gio.TlsConnection.TlsConnectionSetRehandshakeModeMethodInfo
ResolveTlsClientConnectionMethod "setRequireCloseNotify" o = Gio.TlsConnection.TlsConnectionSetRequireCloseNotifyMethodInfo
ResolveTlsClientConnectionMethod "setServerIdentity" o = TlsClientConnectionSetServerIdentityMethodInfo
ResolveTlsClientConnectionMethod "setUseSsl3" o = TlsClientConnectionSetUseSsl3MethodInfo
ResolveTlsClientConnectionMethod "setUseSystemCertdb" o = Gio.TlsConnection.TlsConnectionSetUseSystemCertdbMethodInfo
ResolveTlsClientConnectionMethod "setValidationFlags" o = TlsClientConnectionSetValidationFlagsMethodInfo
ResolveTlsClientConnectionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTlsClientConnectionMethod t TlsClientConnection, O.MethodInfo info TlsClientConnection p) => OL.IsLabel t (TlsClientConnection -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "g_tls_client_connection_copy_session_state" g_tls_client_connection_copy_session_state ::
Ptr TlsClientConnection ->
Ptr TlsClientConnection ->
IO ()
tlsClientConnectionCopySessionState ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a, IsTlsClientConnection b) =>
a
-> b
-> m ()
tlsClientConnectionCopySessionState :: a -> b -> m ()
tlsClientConnectionCopySessionState a
conn b
source = 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 TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsClientConnection
source' <- b -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
source
Ptr TlsClientConnection -> Ptr TlsClientConnection -> IO ()
g_tls_client_connection_copy_session_state Ptr TlsClientConnection
conn' Ptr TlsClientConnection
source'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
source
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionCopySessionStateMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTlsClientConnection a, IsTlsClientConnection b) => O.MethodInfo TlsClientConnectionCopySessionStateMethodInfo a signature where
overloadedMethod = tlsClientConnectionCopySessionState
#endif
foreign import ccall "g_tls_client_connection_get_accepted_cas" g_tls_client_connection_get_accepted_cas ::
Ptr TlsClientConnection ->
IO (Ptr (GList (Ptr GByteArray)))
tlsClientConnectionGetAcceptedCas ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
a
-> m [ByteString]
tlsClientConnectionGetAcceptedCas :: a -> m [ByteString]
tlsClientConnectionGetAcceptedCas a
conn = 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
Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr (GList (Ptr GByteArray))
result <- Ptr TlsClientConnection -> IO (Ptr (GList (Ptr GByteArray)))
g_tls_client_connection_get_accepted_cas Ptr TlsClientConnection
conn'
[Ptr GByteArray]
result' <- Ptr (GList (Ptr GByteArray)) -> IO [Ptr GByteArray]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr GByteArray))
result
[ByteString]
result'' <- (Ptr GByteArray -> IO ByteString)
-> [Ptr GByteArray] -> IO [ByteString]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Ptr GByteArray -> IO ByteString
unpackGByteArray [Ptr GByteArray]
result'
(Ptr GByteArray -> IO ()) -> Ptr (GList (Ptr GByteArray)) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (GList (Ptr a)) -> IO ()
mapGList Ptr GByteArray -> IO ()
unrefGByteArray Ptr (GList (Ptr GByteArray))
result
Ptr (GList (Ptr GByteArray)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr GByteArray))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
[ByteString] -> IO [ByteString]
forall (m :: * -> *) a. Monad m => a -> m a
return [ByteString]
result''
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionGetAcceptedCasMethodInfo
instance (signature ~ (m [ByteString]), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionGetAcceptedCasMethodInfo a signature where
overloadedMethod = tlsClientConnectionGetAcceptedCas
#endif
foreign import ccall "g_tls_client_connection_get_server_identity" g_tls_client_connection_get_server_identity ::
Ptr TlsClientConnection ->
IO (Ptr Gio.SocketConnectable.SocketConnectable)
tlsClientConnectionGetServerIdentity ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
a
-> m Gio.SocketConnectable.SocketConnectable
tlsClientConnectionGetServerIdentity :: a -> m SocketConnectable
tlsClientConnectionGetServerIdentity a
conn = IO SocketConnectable -> m SocketConnectable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketConnectable -> m SocketConnectable)
-> IO SocketConnectable -> m SocketConnectable
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr SocketConnectable
result <- Ptr TlsClientConnection -> IO (Ptr SocketConnectable)
g_tls_client_connection_get_server_identity Ptr TlsClientConnection
conn'
Text -> Ptr SocketConnectable -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsClientConnectionGetServerIdentity" Ptr SocketConnectable
result
SocketConnectable
result' <- ((ManagedPtr SocketConnectable -> SocketConnectable)
-> Ptr SocketConnectable -> IO SocketConnectable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr SocketConnectable -> SocketConnectable
Gio.SocketConnectable.SocketConnectable) Ptr SocketConnectable
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
SocketConnectable -> IO SocketConnectable
forall (m :: * -> *) a. Monad m => a -> m a
return SocketConnectable
result'
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionGetServerIdentityMethodInfo
instance (signature ~ (m Gio.SocketConnectable.SocketConnectable), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionGetServerIdentityMethodInfo a signature where
overloadedMethod = tlsClientConnectionGetServerIdentity
#endif
foreign import ccall "g_tls_client_connection_get_use_ssl3" g_tls_client_connection_get_use_ssl3 ::
Ptr TlsClientConnection ->
IO CInt
{-# DEPRECATED tlsClientConnectionGetUseSsl3 ["(Since version 2.56)","SSL 3.0 is insecure."] #-}
tlsClientConnectionGetUseSsl3 ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
a
-> m Bool
tlsClientConnectionGetUseSsl3 :: a -> m Bool
tlsClientConnectionGetUseSsl3 a
conn = 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 TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
CInt
result <- Ptr TlsClientConnection -> IO CInt
g_tls_client_connection_get_use_ssl3 Ptr TlsClientConnection
conn'
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
conn
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionGetUseSsl3MethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionGetUseSsl3MethodInfo a signature where
overloadedMethod = tlsClientConnectionGetUseSsl3
#endif
foreign import ccall "g_tls_client_connection_get_validation_flags" g_tls_client_connection_get_validation_flags ::
Ptr TlsClientConnection ->
IO CUInt
tlsClientConnectionGetValidationFlags ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
a
-> m [Gio.Flags.TlsCertificateFlags]
tlsClientConnectionGetValidationFlags :: a -> m [TlsCertificateFlags]
tlsClientConnectionGetValidationFlags a
conn = IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TlsCertificateFlags] -> m [TlsCertificateFlags])
-> IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
CUInt
result <- Ptr TlsClientConnection -> IO CUInt
g_tls_client_connection_get_validation_flags Ptr TlsClientConnection
conn'
let result' :: [TlsCertificateFlags]
result' = CUInt -> [TlsCertificateFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
[TlsCertificateFlags] -> IO [TlsCertificateFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [TlsCertificateFlags]
result'
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionGetValidationFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.TlsCertificateFlags]), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionGetValidationFlagsMethodInfo a signature where
overloadedMethod = tlsClientConnectionGetValidationFlags
#endif
foreign import ccall "g_tls_client_connection_set_server_identity" g_tls_client_connection_set_server_identity ::
Ptr TlsClientConnection ->
Ptr Gio.SocketConnectable.SocketConnectable ->
IO ()
tlsClientConnectionSetServerIdentity ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a, Gio.SocketConnectable.IsSocketConnectable b) =>
a
-> b
-> m ()
tlsClientConnectionSetServerIdentity :: a -> b -> m ()
tlsClientConnectionSetServerIdentity a
conn b
identity = 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 TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr SocketConnectable
identity' <- b -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
identity
Ptr TlsClientConnection -> Ptr SocketConnectable -> IO ()
g_tls_client_connection_set_server_identity Ptr TlsClientConnection
conn' Ptr SocketConnectable
identity'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
identity
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionSetServerIdentityMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTlsClientConnection a, Gio.SocketConnectable.IsSocketConnectable b) => O.MethodInfo TlsClientConnectionSetServerIdentityMethodInfo a signature where
overloadedMethod = tlsClientConnectionSetServerIdentity
#endif
foreign import ccall "g_tls_client_connection_set_use_ssl3" g_tls_client_connection_set_use_ssl3 ::
Ptr TlsClientConnection ->
CInt ->
IO ()
{-# DEPRECATED tlsClientConnectionSetUseSsl3 ["(Since version 2.56)","SSL 3.0 is insecure."] #-}
tlsClientConnectionSetUseSsl3 ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
a
-> Bool
-> m ()
tlsClientConnectionSetUseSsl3 :: a -> Bool -> m ()
tlsClientConnectionSetUseSsl3 a
conn Bool
useSsl3 = 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 TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let useSsl3' :: CInt
useSsl3' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
useSsl3
Ptr TlsClientConnection -> CInt -> IO ()
g_tls_client_connection_set_use_ssl3 Ptr TlsClientConnection
conn' CInt
useSsl3'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionSetUseSsl3MethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionSetUseSsl3MethodInfo a signature where
overloadedMethod = tlsClientConnectionSetUseSsl3
#endif
foreign import ccall "g_tls_client_connection_set_validation_flags" g_tls_client_connection_set_validation_flags ::
Ptr TlsClientConnection ->
CUInt ->
IO ()
tlsClientConnectionSetValidationFlags ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
a
-> [Gio.Flags.TlsCertificateFlags]
-> m ()
tlsClientConnectionSetValidationFlags :: a -> [TlsCertificateFlags] -> m ()
tlsClientConnectionSetValidationFlags a
conn [TlsCertificateFlags]
flags = 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 TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let flags' :: CUInt
flags' = [TlsCertificateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TlsCertificateFlags]
flags
Ptr TlsClientConnection -> CUInt -> IO ()
g_tls_client_connection_set_validation_flags Ptr TlsClientConnection
conn' CUInt
flags'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionSetValidationFlagsMethodInfo
instance (signature ~ ([Gio.Flags.TlsCertificateFlags] -> m ()), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionSetValidationFlagsMethodInfo a signature where
overloadedMethod = tlsClientConnectionSetValidationFlags
#endif
foreign import ccall "g_tls_client_connection_new" g_tls_client_connection_new ::
Ptr Gio.IOStream.IOStream ->
Ptr Gio.SocketConnectable.SocketConnectable ->
Ptr (Ptr GError) ->
IO (Ptr TlsClientConnection)
tlsClientConnectionNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.IOStream.IsIOStream a, Gio.SocketConnectable.IsSocketConnectable b) =>
a
-> Maybe (b)
-> m TlsClientConnection
tlsClientConnectionNew :: a -> Maybe b -> m TlsClientConnection
tlsClientConnectionNew a
baseIoStream Maybe b
serverIdentity = IO TlsClientConnection -> m TlsClientConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsClientConnection -> m TlsClientConnection)
-> IO TlsClientConnection -> m TlsClientConnection
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 SocketConnectable
maybeServerIdentity <- case Maybe b
serverIdentity of
Maybe b
Nothing -> Ptr SocketConnectable -> IO (Ptr SocketConnectable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketConnectable
forall a. Ptr a
nullPtr
Just b
jServerIdentity -> do
Ptr SocketConnectable
jServerIdentity' <- b -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jServerIdentity
Ptr SocketConnectable -> IO (Ptr SocketConnectable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketConnectable
jServerIdentity'
IO TlsClientConnection -> IO () -> IO TlsClientConnection
forall a b. IO a -> IO b -> IO a
onException (do
Ptr TlsClientConnection
result <- (Ptr (Ptr GError) -> IO (Ptr TlsClientConnection))
-> IO (Ptr TlsClientConnection)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr TlsClientConnection))
-> IO (Ptr TlsClientConnection))
-> (Ptr (Ptr GError) -> IO (Ptr TlsClientConnection))
-> IO (Ptr TlsClientConnection)
forall a b. (a -> b) -> a -> b
$ Ptr IOStream
-> Ptr SocketConnectable
-> Ptr (Ptr GError)
-> IO (Ptr TlsClientConnection)
g_tls_client_connection_new Ptr IOStream
baseIoStream' Ptr SocketConnectable
maybeServerIdentity
Text -> Ptr TlsClientConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsClientConnectionNew" Ptr TlsClientConnection
result
TlsClientConnection
result' <- ((ManagedPtr TlsClientConnection -> TlsClientConnection)
-> Ptr TlsClientConnection -> IO TlsClientConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsClientConnection -> TlsClientConnection
TlsClientConnection) Ptr TlsClientConnection
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
baseIoStream
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
serverIdentity b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
TlsClientConnection -> IO TlsClientConnection
forall (m :: * -> *) a. Monad m => a -> m a
return TlsClientConnection
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TlsClientConnection = TlsClientConnectionSignalList
type TlsClientConnectionSignalList = ('[ '("acceptCertificate", Gio.TlsConnection.TlsConnectionAcceptCertificateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif