{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.TlsConnection
(
TlsConnection(..) ,
IsTlsConnection ,
toTlsConnection ,
#if defined(ENABLE_OVERLOADING)
ResolveTlsConnectionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionEmitAcceptCertificateMethodInfo,
#endif
tlsConnectionEmitAcceptCertificate ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetCertificateMethodInfo ,
#endif
tlsConnectionGetCertificate ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetDatabaseMethodInfo ,
#endif
tlsConnectionGetDatabase ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetInteractionMethodInfo ,
#endif
tlsConnectionGetInteraction ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetNegotiatedProtocolMethodInfo,
#endif
tlsConnectionGetNegotiatedProtocol ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetPeerCertificateMethodInfo,
#endif
tlsConnectionGetPeerCertificate ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetPeerCertificateErrorsMethodInfo,
#endif
tlsConnectionGetPeerCertificateErrors ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetRehandshakeModeMethodInfo,
#endif
tlsConnectionGetRehandshakeMode ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetRequireCloseNotifyMethodInfo,
#endif
tlsConnectionGetRequireCloseNotify ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionGetUseSystemCertdbMethodInfo,
#endif
tlsConnectionGetUseSystemCertdb ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionHandshakeMethodInfo ,
#endif
tlsConnectionHandshake ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionHandshakeAsyncMethodInfo ,
#endif
tlsConnectionHandshakeAsync ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionHandshakeFinishMethodInfo ,
#endif
tlsConnectionHandshakeFinish ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionSetAdvertisedProtocolsMethodInfo,
#endif
tlsConnectionSetAdvertisedProtocols ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionSetCertificateMethodInfo ,
#endif
tlsConnectionSetCertificate ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionSetDatabaseMethodInfo ,
#endif
tlsConnectionSetDatabase ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionSetInteractionMethodInfo ,
#endif
tlsConnectionSetInteraction ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionSetRehandshakeModeMethodInfo,
#endif
tlsConnectionSetRehandshakeMode ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionSetRequireCloseNotifyMethodInfo,
#endif
tlsConnectionSetRequireCloseNotify ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionSetUseSystemCertdbMethodInfo,
#endif
tlsConnectionSetUseSystemCertdb ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionAdvertisedProtocolsPropertyInfo,
#endif
clearTlsConnectionAdvertisedProtocols ,
constructTlsConnectionAdvertisedProtocols,
getTlsConnectionAdvertisedProtocols ,
setTlsConnectionAdvertisedProtocols ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionAdvertisedProtocols ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionBaseIoStreamPropertyInfo ,
#endif
constructTlsConnectionBaseIoStream ,
getTlsConnectionBaseIoStream ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionBaseIoStream ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionCertificatePropertyInfo ,
#endif
constructTlsConnectionCertificate ,
getTlsConnectionCertificate ,
setTlsConnectionCertificate ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionCertificate ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionDatabasePropertyInfo ,
#endif
constructTlsConnectionDatabase ,
getTlsConnectionDatabase ,
setTlsConnectionDatabase ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionDatabase ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionInteractionPropertyInfo ,
#endif
clearTlsConnectionInteraction ,
constructTlsConnectionInteraction ,
getTlsConnectionInteraction ,
setTlsConnectionInteraction ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionInteraction ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionNegotiatedProtocolPropertyInfo,
#endif
getTlsConnectionNegotiatedProtocol ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionNegotiatedProtocol ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionPeerCertificatePropertyInfo,
#endif
getTlsConnectionPeerCertificate ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionPeerCertificate ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionPeerCertificateErrorsPropertyInfo,
#endif
getTlsConnectionPeerCertificateErrors ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionPeerCertificateErrors ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionRehandshakeModePropertyInfo,
#endif
constructTlsConnectionRehandshakeMode ,
getTlsConnectionRehandshakeMode ,
setTlsConnectionRehandshakeMode ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionRehandshakeMode ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionRequireCloseNotifyPropertyInfo,
#endif
constructTlsConnectionRequireCloseNotify,
getTlsConnectionRequireCloseNotify ,
setTlsConnectionRequireCloseNotify ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionRequireCloseNotify ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsConnectionUseSystemCertdbPropertyInfo,
#endif
constructTlsConnectionUseSystemCertdb ,
getTlsConnectionUseSystemCertdb ,
setTlsConnectionUseSystemCertdb ,
#if defined(ENABLE_OVERLOADING)
tlsConnectionUseSystemCertdb ,
#endif
C_TlsConnectionAcceptCertificateCallback,
TlsConnectionAcceptCertificateCallback ,
#if defined(ENABLE_OVERLOADING)
TlsConnectionAcceptCertificateSignalInfo,
#endif
afterTlsConnectionAcceptCertificate ,
genClosure_TlsConnectionAcceptCertificate,
mk_TlsConnectionAcceptCertificateCallback,
noTlsConnectionAcceptCertificateCallback,
onTlsConnectionAcceptCertificate ,
wrap_TlsConnectionAcceptCertificateCallback,
) 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 qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsCertificate as Gio.TlsCertificate
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsDatabase as Gio.TlsDatabase
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsInteraction as Gio.TlsInteraction
newtype TlsConnection = TlsConnection (SP.ManagedPtr TlsConnection)
deriving (TlsConnection -> TlsConnection -> Bool
(TlsConnection -> TlsConnection -> Bool)
-> (TlsConnection -> TlsConnection -> Bool) -> Eq TlsConnection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsConnection -> TlsConnection -> Bool
$c/= :: TlsConnection -> TlsConnection -> Bool
== :: TlsConnection -> TlsConnection -> Bool
$c== :: TlsConnection -> TlsConnection -> Bool
Eq)
instance SP.ManagedPtrNewtype TlsConnection where
toManagedPtr :: TlsConnection -> ManagedPtr TlsConnection
toManagedPtr (TlsConnection ManagedPtr TlsConnection
p) = ManagedPtr TlsConnection
p
foreign import ccall "g_tls_connection_get_type"
c_g_tls_connection_get_type :: IO B.Types.GType
instance B.Types.TypedObject TlsConnection where
glibType :: IO GType
glibType = IO GType
c_g_tls_connection_get_type
instance B.Types.GObject TlsConnection
instance B.GValue.IsGValue TlsConnection where
toGValue :: TlsConnection -> IO GValue
toGValue TlsConnection
o = do
GType
gtype <- IO GType
c_g_tls_connection_get_type
TlsConnection -> (Ptr TlsConnection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsConnection
o (GType
-> (GValue -> Ptr TlsConnection -> IO ())
-> Ptr TlsConnection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TlsConnection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO TlsConnection
fromGValue GValue
gv = do
Ptr TlsConnection
ptr <- GValue -> IO (Ptr TlsConnection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TlsConnection)
(ManagedPtr TlsConnection -> TlsConnection)
-> Ptr TlsConnection -> IO TlsConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TlsConnection -> TlsConnection
TlsConnection Ptr TlsConnection
ptr
class (SP.GObject o, O.IsDescendantOf TlsConnection o) => IsTlsConnection o
instance (SP.GObject o, O.IsDescendantOf TlsConnection o) => IsTlsConnection o
instance O.HasParentTypes TlsConnection
type instance O.ParentTypes TlsConnection = '[Gio.IOStream.IOStream, GObject.Object.Object]
toTlsConnection :: (MonadIO m, IsTlsConnection o) => o -> m TlsConnection
toTlsConnection :: o -> m TlsConnection
toTlsConnection = IO TlsConnection -> m TlsConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsConnection -> m TlsConnection)
-> (o -> IO TlsConnection) -> o -> m TlsConnection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TlsConnection -> TlsConnection)
-> o -> IO TlsConnection
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TlsConnection -> TlsConnection
TlsConnection
#if defined(ENABLE_OVERLOADING)
type family ResolveTlsConnectionMethod (t :: Symbol) (o :: *) :: * where
ResolveTlsConnectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTlsConnectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTlsConnectionMethod "clearPending" o = Gio.IOStream.IOStreamClearPendingMethodInfo
ResolveTlsConnectionMethod "close" o = Gio.IOStream.IOStreamCloseMethodInfo
ResolveTlsConnectionMethod "closeAsync" o = Gio.IOStream.IOStreamCloseAsyncMethodInfo
ResolveTlsConnectionMethod "closeFinish" o = Gio.IOStream.IOStreamCloseFinishMethodInfo
ResolveTlsConnectionMethod "emitAcceptCertificate" o = TlsConnectionEmitAcceptCertificateMethodInfo
ResolveTlsConnectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTlsConnectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTlsConnectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTlsConnectionMethod "handshake" o = TlsConnectionHandshakeMethodInfo
ResolveTlsConnectionMethod "handshakeAsync" o = TlsConnectionHandshakeAsyncMethodInfo
ResolveTlsConnectionMethod "handshakeFinish" o = TlsConnectionHandshakeFinishMethodInfo
ResolveTlsConnectionMethod "hasPending" o = Gio.IOStream.IOStreamHasPendingMethodInfo
ResolveTlsConnectionMethod "isClosed" o = Gio.IOStream.IOStreamIsClosedMethodInfo
ResolveTlsConnectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTlsConnectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTlsConnectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTlsConnectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTlsConnectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTlsConnectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTlsConnectionMethod "spliceAsync" o = Gio.IOStream.IOStreamSpliceAsyncMethodInfo
ResolveTlsConnectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTlsConnectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTlsConnectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTlsConnectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTlsConnectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTlsConnectionMethod "getCertificate" o = TlsConnectionGetCertificateMethodInfo
ResolveTlsConnectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTlsConnectionMethod "getDatabase" o = TlsConnectionGetDatabaseMethodInfo
ResolveTlsConnectionMethod "getInputStream" o = Gio.IOStream.IOStreamGetInputStreamMethodInfo
ResolveTlsConnectionMethod "getInteraction" o = TlsConnectionGetInteractionMethodInfo
ResolveTlsConnectionMethod "getNegotiatedProtocol" o = TlsConnectionGetNegotiatedProtocolMethodInfo
ResolveTlsConnectionMethod "getOutputStream" o = Gio.IOStream.IOStreamGetOutputStreamMethodInfo
ResolveTlsConnectionMethod "getPeerCertificate" o = TlsConnectionGetPeerCertificateMethodInfo
ResolveTlsConnectionMethod "getPeerCertificateErrors" o = TlsConnectionGetPeerCertificateErrorsMethodInfo
ResolveTlsConnectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTlsConnectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTlsConnectionMethod "getRehandshakeMode" o = TlsConnectionGetRehandshakeModeMethodInfo
ResolveTlsConnectionMethod "getRequireCloseNotify" o = TlsConnectionGetRequireCloseNotifyMethodInfo
ResolveTlsConnectionMethod "getUseSystemCertdb" o = TlsConnectionGetUseSystemCertdbMethodInfo
ResolveTlsConnectionMethod "setAdvertisedProtocols" o = TlsConnectionSetAdvertisedProtocolsMethodInfo
ResolveTlsConnectionMethod "setCertificate" o = TlsConnectionSetCertificateMethodInfo
ResolveTlsConnectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTlsConnectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTlsConnectionMethod "setDatabase" o = TlsConnectionSetDatabaseMethodInfo
ResolveTlsConnectionMethod "setInteraction" o = TlsConnectionSetInteractionMethodInfo
ResolveTlsConnectionMethod "setPending" o = Gio.IOStream.IOStreamSetPendingMethodInfo
ResolveTlsConnectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTlsConnectionMethod "setRehandshakeMode" o = TlsConnectionSetRehandshakeModeMethodInfo
ResolveTlsConnectionMethod "setRequireCloseNotify" o = TlsConnectionSetRequireCloseNotifyMethodInfo
ResolveTlsConnectionMethod "setUseSystemCertdb" o = TlsConnectionSetUseSystemCertdbMethodInfo
ResolveTlsConnectionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTlsConnectionMethod t TlsConnection, O.MethodInfo info TlsConnection p) => OL.IsLabel t (TlsConnection -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
type TlsConnectionAcceptCertificateCallback =
Gio.TlsCertificate.TlsCertificate
-> [Gio.Flags.TlsCertificateFlags]
-> IO Bool
noTlsConnectionAcceptCertificateCallback :: Maybe TlsConnectionAcceptCertificateCallback
noTlsConnectionAcceptCertificateCallback :: Maybe TlsConnectionAcceptCertificateCallback
noTlsConnectionAcceptCertificateCallback = Maybe TlsConnectionAcceptCertificateCallback
forall a. Maybe a
Nothing
type C_TlsConnectionAcceptCertificateCallback =
Ptr () ->
Ptr Gio.TlsCertificate.TlsCertificate ->
CUInt ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_TlsConnectionAcceptCertificateCallback :: C_TlsConnectionAcceptCertificateCallback -> IO (FunPtr C_TlsConnectionAcceptCertificateCallback)
genClosure_TlsConnectionAcceptCertificate :: MonadIO m => TlsConnectionAcceptCertificateCallback -> m (GClosure C_TlsConnectionAcceptCertificateCallback)
genClosure_TlsConnectionAcceptCertificate :: TlsConnectionAcceptCertificateCallback
-> m (GClosure C_TlsConnectionAcceptCertificateCallback)
genClosure_TlsConnectionAcceptCertificate TlsConnectionAcceptCertificateCallback
cb = IO (GClosure C_TlsConnectionAcceptCertificateCallback)
-> m (GClosure C_TlsConnectionAcceptCertificateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TlsConnectionAcceptCertificateCallback)
-> m (GClosure C_TlsConnectionAcceptCertificateCallback))
-> IO (GClosure C_TlsConnectionAcceptCertificateCallback)
-> m (GClosure C_TlsConnectionAcceptCertificateCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_TlsConnectionAcceptCertificateCallback
cb' = TlsConnectionAcceptCertificateCallback
-> C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback TlsConnectionAcceptCertificateCallback
cb
C_TlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_TlsConnectionAcceptCertificateCallback)
mk_TlsConnectionAcceptCertificateCallback C_TlsConnectionAcceptCertificateCallback
cb' IO (FunPtr C_TlsConnectionAcceptCertificateCallback)
-> (FunPtr C_TlsConnectionAcceptCertificateCallback
-> IO (GClosure C_TlsConnectionAcceptCertificateCallback))
-> IO (GClosure C_TlsConnectionAcceptCertificateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TlsConnectionAcceptCertificateCallback
-> IO (GClosure C_TlsConnectionAcceptCertificateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TlsConnectionAcceptCertificateCallback ::
TlsConnectionAcceptCertificateCallback ->
C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback :: TlsConnectionAcceptCertificateCallback
-> C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback TlsConnectionAcceptCertificateCallback
_cb Ptr ()
_ Ptr TlsCertificate
peerCert CUInt
errors Ptr ()
_ = do
TlsCertificate
peerCert' <- ((ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TlsCertificate -> TlsCertificate
Gio.TlsCertificate.TlsCertificate) Ptr TlsCertificate
peerCert
let errors' :: [TlsCertificateFlags]
errors' = CUInt -> [TlsCertificateFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
errors
Bool
result <- TlsConnectionAcceptCertificateCallback
_cb TlsCertificate
peerCert' [TlsCertificateFlags]
errors'
let result' :: CInt
result' = (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
result
CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onTlsConnectionAcceptCertificate :: (IsTlsConnection a, MonadIO m) => a -> TlsConnectionAcceptCertificateCallback -> m SignalHandlerId
onTlsConnectionAcceptCertificate :: a -> TlsConnectionAcceptCertificateCallback -> m SignalHandlerId
onTlsConnectionAcceptCertificate a
obj TlsConnectionAcceptCertificateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_TlsConnectionAcceptCertificateCallback
cb' = TlsConnectionAcceptCertificateCallback
-> C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback TlsConnectionAcceptCertificateCallback
cb
FunPtr C_TlsConnectionAcceptCertificateCallback
cb'' <- C_TlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_TlsConnectionAcceptCertificateCallback)
mk_TlsConnectionAcceptCertificateCallback C_TlsConnectionAcceptCertificateCallback
cb'
a
-> Text
-> FunPtr C_TlsConnectionAcceptCertificateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"accept-certificate" FunPtr C_TlsConnectionAcceptCertificateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTlsConnectionAcceptCertificate :: (IsTlsConnection a, MonadIO m) => a -> TlsConnectionAcceptCertificateCallback -> m SignalHandlerId
afterTlsConnectionAcceptCertificate :: a -> TlsConnectionAcceptCertificateCallback -> m SignalHandlerId
afterTlsConnectionAcceptCertificate a
obj TlsConnectionAcceptCertificateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_TlsConnectionAcceptCertificateCallback
cb' = TlsConnectionAcceptCertificateCallback
-> C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback TlsConnectionAcceptCertificateCallback
cb
FunPtr C_TlsConnectionAcceptCertificateCallback
cb'' <- C_TlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_TlsConnectionAcceptCertificateCallback)
mk_TlsConnectionAcceptCertificateCallback C_TlsConnectionAcceptCertificateCallback
cb'
a
-> Text
-> FunPtr C_TlsConnectionAcceptCertificateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"accept-certificate" FunPtr C_TlsConnectionAcceptCertificateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TlsConnectionAcceptCertificateSignalInfo
instance SignalInfo TlsConnectionAcceptCertificateSignalInfo where
type HaskellCallbackType TlsConnectionAcceptCertificateSignalInfo = TlsConnectionAcceptCertificateCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_TlsConnectionAcceptCertificateCallback cb
cb'' <- mk_TlsConnectionAcceptCertificateCallback cb'
connectSignalFunPtr obj "accept-certificate" cb'' connectMode detail
#endif
getTlsConnectionAdvertisedProtocols :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe [T.Text])
getTlsConnectionAdvertisedProtocols :: o -> m (Maybe [Text])
getTlsConnectionAdvertisedProtocols o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj String
"advertised-protocols"
setTlsConnectionAdvertisedProtocols :: (MonadIO m, IsTlsConnection o) => o -> [T.Text] -> m ()
setTlsConnectionAdvertisedProtocols :: o -> [Text] -> m ()
setTlsConnectionAdvertisedProtocols o
obj [Text]
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 [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"advertised-protocols" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructTlsConnectionAdvertisedProtocols :: (IsTlsConnection o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructTlsConnectionAdvertisedProtocols :: [Text] -> m (GValueConstruct o)
constructTlsConnectionAdvertisedProtocols [Text]
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 [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray String
"advertised-protocols" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearTlsConnectionAdvertisedProtocols :: (MonadIO m, IsTlsConnection o) => o -> m ()
clearTlsConnectionAdvertisedProtocols :: o -> m ()
clearTlsConnectionAdvertisedProtocols o
obj = 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 [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"advertised-protocols" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data TlsConnectionAdvertisedProtocolsPropertyInfo
instance AttrInfo TlsConnectionAdvertisedProtocolsPropertyInfo where
type AttrAllowedOps TlsConnectionAdvertisedProtocolsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint TlsConnectionAdvertisedProtocolsPropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionAdvertisedProtocolsPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint TlsConnectionAdvertisedProtocolsPropertyInfo = (~) [T.Text]
type AttrTransferType TlsConnectionAdvertisedProtocolsPropertyInfo = [T.Text]
type AttrGetType TlsConnectionAdvertisedProtocolsPropertyInfo = (Maybe [T.Text])
type AttrLabel TlsConnectionAdvertisedProtocolsPropertyInfo = "advertised-protocols"
type AttrOrigin TlsConnectionAdvertisedProtocolsPropertyInfo = TlsConnection
attrGet = getTlsConnectionAdvertisedProtocols
attrSet = setTlsConnectionAdvertisedProtocols
attrTransfer _ v = do
return v
attrConstruct = constructTlsConnectionAdvertisedProtocols
attrClear = clearTlsConnectionAdvertisedProtocols
#endif
getTlsConnectionBaseIoStream :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe Gio.IOStream.IOStream)
getTlsConnectionBaseIoStream :: o -> m (Maybe IOStream)
getTlsConnectionBaseIoStream o
obj = IO (Maybe IOStream) -> m (Maybe IOStream)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IOStream) -> m (Maybe IOStream))
-> IO (Maybe IOStream) -> m (Maybe 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
constructTlsConnectionBaseIoStream :: (IsTlsConnection o, MIO.MonadIO m, Gio.IOStream.IsIOStream a) => a -> m (GValueConstruct o)
constructTlsConnectionBaseIoStream :: a -> m (GValueConstruct o)
constructTlsConnectionBaseIoStream 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 TlsConnectionBaseIoStreamPropertyInfo
instance AttrInfo TlsConnectionBaseIoStreamPropertyInfo where
type AttrAllowedOps TlsConnectionBaseIoStreamPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint TlsConnectionBaseIoStreamPropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionBaseIoStreamPropertyInfo = Gio.IOStream.IsIOStream
type AttrTransferTypeConstraint TlsConnectionBaseIoStreamPropertyInfo = Gio.IOStream.IsIOStream
type AttrTransferType TlsConnectionBaseIoStreamPropertyInfo = Gio.IOStream.IOStream
type AttrGetType TlsConnectionBaseIoStreamPropertyInfo = (Maybe Gio.IOStream.IOStream)
type AttrLabel TlsConnectionBaseIoStreamPropertyInfo = "base-io-stream"
type AttrOrigin TlsConnectionBaseIoStreamPropertyInfo = TlsConnection
attrGet = getTlsConnectionBaseIoStream
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gio.IOStream.IOStream v
attrConstruct = constructTlsConnectionBaseIoStream
attrClear = undefined
#endif
getTlsConnectionCertificate :: (MonadIO m, IsTlsConnection o) => o -> m Gio.TlsCertificate.TlsCertificate
getTlsConnectionCertificate :: o -> m TlsCertificate
getTlsConnectionCertificate o
obj = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsCertificate -> m TlsCertificate)
-> IO TlsCertificate -> m TlsCertificate
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe TlsCertificate) -> IO TlsCertificate
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTlsConnectionCertificate" (IO (Maybe TlsCertificate) -> IO TlsCertificate)
-> IO (Maybe TlsCertificate) -> IO TlsCertificate
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TlsCertificate -> TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"certificate" ManagedPtr TlsCertificate -> TlsCertificate
Gio.TlsCertificate.TlsCertificate
setTlsConnectionCertificate :: (MonadIO m, IsTlsConnection o, Gio.TlsCertificate.IsTlsCertificate a) => o -> a -> m ()
setTlsConnectionCertificate :: o -> a -> m ()
setTlsConnectionCertificate 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
"certificate" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTlsConnectionCertificate :: (IsTlsConnection o, MIO.MonadIO m, Gio.TlsCertificate.IsTlsCertificate a) => a -> m (GValueConstruct o)
constructTlsConnectionCertificate :: a -> m (GValueConstruct o)
constructTlsConnectionCertificate 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
"certificate" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data TlsConnectionCertificatePropertyInfo
instance AttrInfo TlsConnectionCertificatePropertyInfo where
type AttrAllowedOps TlsConnectionCertificatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsConnectionCertificatePropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionCertificatePropertyInfo = Gio.TlsCertificate.IsTlsCertificate
type AttrTransferTypeConstraint TlsConnectionCertificatePropertyInfo = Gio.TlsCertificate.IsTlsCertificate
type AttrTransferType TlsConnectionCertificatePropertyInfo = Gio.TlsCertificate.TlsCertificate
type AttrGetType TlsConnectionCertificatePropertyInfo = Gio.TlsCertificate.TlsCertificate
type AttrLabel TlsConnectionCertificatePropertyInfo = "certificate"
type AttrOrigin TlsConnectionCertificatePropertyInfo = TlsConnection
attrGet = getTlsConnectionCertificate
attrSet = setTlsConnectionCertificate
attrTransfer _ v = do
unsafeCastTo Gio.TlsCertificate.TlsCertificate v
attrConstruct = constructTlsConnectionCertificate
attrClear = undefined
#endif
getTlsConnectionDatabase :: (MonadIO m, IsTlsConnection o) => o -> m Gio.TlsDatabase.TlsDatabase
getTlsConnectionDatabase :: o -> m TlsDatabase
getTlsConnectionDatabase o
obj = IO TlsDatabase -> m TlsDatabase
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsDatabase -> m TlsDatabase)
-> IO TlsDatabase -> m TlsDatabase
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe TlsDatabase) -> IO TlsDatabase
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTlsConnectionDatabase" (IO (Maybe TlsDatabase) -> IO TlsDatabase)
-> IO (Maybe TlsDatabase) -> IO TlsDatabase
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TlsDatabase -> TlsDatabase)
-> IO (Maybe TlsDatabase)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"database" ManagedPtr TlsDatabase -> TlsDatabase
Gio.TlsDatabase.TlsDatabase
setTlsConnectionDatabase :: (MonadIO m, IsTlsConnection o, Gio.TlsDatabase.IsTlsDatabase a) => o -> a -> m ()
setTlsConnectionDatabase :: o -> a -> m ()
setTlsConnectionDatabase 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
"database" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTlsConnectionDatabase :: (IsTlsConnection o, MIO.MonadIO m, Gio.TlsDatabase.IsTlsDatabase a) => a -> m (GValueConstruct o)
constructTlsConnectionDatabase :: a -> m (GValueConstruct o)
constructTlsConnectionDatabase 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
"database" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data TlsConnectionDatabasePropertyInfo
instance AttrInfo TlsConnectionDatabasePropertyInfo where
type AttrAllowedOps TlsConnectionDatabasePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsConnectionDatabasePropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionDatabasePropertyInfo = Gio.TlsDatabase.IsTlsDatabase
type AttrTransferTypeConstraint TlsConnectionDatabasePropertyInfo = Gio.TlsDatabase.IsTlsDatabase
type AttrTransferType TlsConnectionDatabasePropertyInfo = Gio.TlsDatabase.TlsDatabase
type AttrGetType TlsConnectionDatabasePropertyInfo = Gio.TlsDatabase.TlsDatabase
type AttrLabel TlsConnectionDatabasePropertyInfo = "database"
type AttrOrigin TlsConnectionDatabasePropertyInfo = TlsConnection
attrGet = getTlsConnectionDatabase
attrSet = setTlsConnectionDatabase
attrTransfer _ v = do
unsafeCastTo Gio.TlsDatabase.TlsDatabase v
attrConstruct = constructTlsConnectionDatabase
attrClear = undefined
#endif
getTlsConnectionInteraction :: (MonadIO m, IsTlsConnection o) => o -> m Gio.TlsInteraction.TlsInteraction
getTlsConnectionInteraction :: o -> m TlsInteraction
getTlsConnectionInteraction o
obj = IO TlsInteraction -> m TlsInteraction
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsInteraction -> m TlsInteraction)
-> IO TlsInteraction -> m TlsInteraction
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe TlsInteraction) -> IO TlsInteraction
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTlsConnectionInteraction" (IO (Maybe TlsInteraction) -> IO TlsInteraction)
-> IO (Maybe TlsInteraction) -> IO TlsInteraction
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TlsInteraction -> TlsInteraction)
-> IO (Maybe TlsInteraction)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"interaction" ManagedPtr TlsInteraction -> TlsInteraction
Gio.TlsInteraction.TlsInteraction
setTlsConnectionInteraction :: (MonadIO m, IsTlsConnection o, Gio.TlsInteraction.IsTlsInteraction a) => o -> a -> m ()
setTlsConnectionInteraction :: o -> a -> m ()
setTlsConnectionInteraction 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
"interaction" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTlsConnectionInteraction :: (IsTlsConnection o, MIO.MonadIO m, Gio.TlsInteraction.IsTlsInteraction a) => a -> m (GValueConstruct o)
constructTlsConnectionInteraction :: a -> m (GValueConstruct o)
constructTlsConnectionInteraction 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
"interaction" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearTlsConnectionInteraction :: (MonadIO m, IsTlsConnection o) => o -> m ()
clearTlsConnectionInteraction :: o -> m ()
clearTlsConnectionInteraction o
obj = 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 TlsInteraction -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"interaction" (Maybe TlsInteraction
forall a. Maybe a
Nothing :: Maybe Gio.TlsInteraction.TlsInteraction)
#if defined(ENABLE_OVERLOADING)
data TlsConnectionInteractionPropertyInfo
instance AttrInfo TlsConnectionInteractionPropertyInfo where
type AttrAllowedOps TlsConnectionInteractionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint TlsConnectionInteractionPropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionInteractionPropertyInfo = Gio.TlsInteraction.IsTlsInteraction
type AttrTransferTypeConstraint TlsConnectionInteractionPropertyInfo = Gio.TlsInteraction.IsTlsInteraction
type AttrTransferType TlsConnectionInteractionPropertyInfo = Gio.TlsInteraction.TlsInteraction
type AttrGetType TlsConnectionInteractionPropertyInfo = Gio.TlsInteraction.TlsInteraction
type AttrLabel TlsConnectionInteractionPropertyInfo = "interaction"
type AttrOrigin TlsConnectionInteractionPropertyInfo = TlsConnection
attrGet = getTlsConnectionInteraction
attrSet = setTlsConnectionInteraction
attrTransfer _ v = do
unsafeCastTo Gio.TlsInteraction.TlsInteraction v
attrConstruct = constructTlsConnectionInteraction
attrClear = clearTlsConnectionInteraction
#endif
getTlsConnectionNegotiatedProtocol :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe T.Text)
getTlsConnectionNegotiatedProtocol :: o -> m (Maybe Text)
getTlsConnectionNegotiatedProtocol o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"negotiated-protocol"
#if defined(ENABLE_OVERLOADING)
data TlsConnectionNegotiatedProtocolPropertyInfo
instance AttrInfo TlsConnectionNegotiatedProtocolPropertyInfo where
type AttrAllowedOps TlsConnectionNegotiatedProtocolPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint TlsConnectionNegotiatedProtocolPropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionNegotiatedProtocolPropertyInfo = (~) ()
type AttrTransferTypeConstraint TlsConnectionNegotiatedProtocolPropertyInfo = (~) ()
type AttrTransferType TlsConnectionNegotiatedProtocolPropertyInfo = ()
type AttrGetType TlsConnectionNegotiatedProtocolPropertyInfo = (Maybe T.Text)
type AttrLabel TlsConnectionNegotiatedProtocolPropertyInfo = "negotiated-protocol"
type AttrOrigin TlsConnectionNegotiatedProtocolPropertyInfo = TlsConnection
attrGet = getTlsConnectionNegotiatedProtocol
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getTlsConnectionPeerCertificate :: (MonadIO m, IsTlsConnection o) => o -> m Gio.TlsCertificate.TlsCertificate
getTlsConnectionPeerCertificate :: o -> m TlsCertificate
getTlsConnectionPeerCertificate o
obj = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsCertificate -> m TlsCertificate)
-> IO TlsCertificate -> m TlsCertificate
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe TlsCertificate) -> IO TlsCertificate
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTlsConnectionPeerCertificate" (IO (Maybe TlsCertificate) -> IO TlsCertificate)
-> IO (Maybe TlsCertificate) -> IO TlsCertificate
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TlsCertificate -> TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"peer-certificate" ManagedPtr TlsCertificate -> TlsCertificate
Gio.TlsCertificate.TlsCertificate
#if defined(ENABLE_OVERLOADING)
data TlsConnectionPeerCertificatePropertyInfo
instance AttrInfo TlsConnectionPeerCertificatePropertyInfo where
type AttrAllowedOps TlsConnectionPeerCertificatePropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint TlsConnectionPeerCertificatePropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionPeerCertificatePropertyInfo = (~) ()
type AttrTransferTypeConstraint TlsConnectionPeerCertificatePropertyInfo = (~) ()
type AttrTransferType TlsConnectionPeerCertificatePropertyInfo = ()
type AttrGetType TlsConnectionPeerCertificatePropertyInfo = Gio.TlsCertificate.TlsCertificate
type AttrLabel TlsConnectionPeerCertificatePropertyInfo = "peer-certificate"
type AttrOrigin TlsConnectionPeerCertificatePropertyInfo = TlsConnection
attrGet = getTlsConnectionPeerCertificate
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getTlsConnectionPeerCertificateErrors :: (MonadIO m, IsTlsConnection o) => o -> m [Gio.Flags.TlsCertificateFlags]
getTlsConnectionPeerCertificateErrors :: o -> m [TlsCertificateFlags]
getTlsConnectionPeerCertificateErrors 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
"peer-certificate-errors"
#if defined(ENABLE_OVERLOADING)
data TlsConnectionPeerCertificateErrorsPropertyInfo
instance AttrInfo TlsConnectionPeerCertificateErrorsPropertyInfo where
type AttrAllowedOps TlsConnectionPeerCertificateErrorsPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint TlsConnectionPeerCertificateErrorsPropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionPeerCertificateErrorsPropertyInfo = (~) ()
type AttrTransferTypeConstraint TlsConnectionPeerCertificateErrorsPropertyInfo = (~) ()
type AttrTransferType TlsConnectionPeerCertificateErrorsPropertyInfo = ()
type AttrGetType TlsConnectionPeerCertificateErrorsPropertyInfo = [Gio.Flags.TlsCertificateFlags]
type AttrLabel TlsConnectionPeerCertificateErrorsPropertyInfo = "peer-certificate-errors"
type AttrOrigin TlsConnectionPeerCertificateErrorsPropertyInfo = TlsConnection
attrGet = getTlsConnectionPeerCertificateErrors
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getTlsConnectionRehandshakeMode :: (MonadIO m, IsTlsConnection o) => o -> m Gio.Enums.TlsRehandshakeMode
getTlsConnectionRehandshakeMode :: o -> m TlsRehandshakeMode
getTlsConnectionRehandshakeMode o
obj = IO TlsRehandshakeMode -> m TlsRehandshakeMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsRehandshakeMode -> m TlsRehandshakeMode)
-> IO TlsRehandshakeMode -> m TlsRehandshakeMode
forall a b. (a -> b) -> a -> b
$ o -> String -> IO TlsRehandshakeMode
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"rehandshake-mode"
setTlsConnectionRehandshakeMode :: (MonadIO m, IsTlsConnection o) => o -> Gio.Enums.TlsRehandshakeMode -> m ()
setTlsConnectionRehandshakeMode :: o -> TlsRehandshakeMode -> m ()
setTlsConnectionRehandshakeMode o
obj TlsRehandshakeMode
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 -> TlsRehandshakeMode -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"rehandshake-mode" TlsRehandshakeMode
val
constructTlsConnectionRehandshakeMode :: (IsTlsConnection o, MIO.MonadIO m) => Gio.Enums.TlsRehandshakeMode -> m (GValueConstruct o)
constructTlsConnectionRehandshakeMode :: TlsRehandshakeMode -> m (GValueConstruct o)
constructTlsConnectionRehandshakeMode TlsRehandshakeMode
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 -> TlsRehandshakeMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"rehandshake-mode" TlsRehandshakeMode
val
#if defined(ENABLE_OVERLOADING)
data TlsConnectionRehandshakeModePropertyInfo
instance AttrInfo TlsConnectionRehandshakeModePropertyInfo where
type AttrAllowedOps TlsConnectionRehandshakeModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsConnectionRehandshakeModePropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionRehandshakeModePropertyInfo = (~) Gio.Enums.TlsRehandshakeMode
type AttrTransferTypeConstraint TlsConnectionRehandshakeModePropertyInfo = (~) Gio.Enums.TlsRehandshakeMode
type AttrTransferType TlsConnectionRehandshakeModePropertyInfo = Gio.Enums.TlsRehandshakeMode
type AttrGetType TlsConnectionRehandshakeModePropertyInfo = Gio.Enums.TlsRehandshakeMode
type AttrLabel TlsConnectionRehandshakeModePropertyInfo = "rehandshake-mode"
type AttrOrigin TlsConnectionRehandshakeModePropertyInfo = TlsConnection
attrGet = getTlsConnectionRehandshakeMode
attrSet = setTlsConnectionRehandshakeMode
attrTransfer _ v = do
return v
attrConstruct = constructTlsConnectionRehandshakeMode
attrClear = undefined
#endif
getTlsConnectionRequireCloseNotify :: (MonadIO m, IsTlsConnection o) => o -> m Bool
getTlsConnectionRequireCloseNotify :: o -> m Bool
getTlsConnectionRequireCloseNotify 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
"require-close-notify"
setTlsConnectionRequireCloseNotify :: (MonadIO m, IsTlsConnection o) => o -> Bool -> m ()
setTlsConnectionRequireCloseNotify :: o -> Bool -> m ()
setTlsConnectionRequireCloseNotify 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
"require-close-notify" Bool
val
constructTlsConnectionRequireCloseNotify :: (IsTlsConnection o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTlsConnectionRequireCloseNotify :: Bool -> m (GValueConstruct o)
constructTlsConnectionRequireCloseNotify 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
"require-close-notify" Bool
val
#if defined(ENABLE_OVERLOADING)
data TlsConnectionRequireCloseNotifyPropertyInfo
instance AttrInfo TlsConnectionRequireCloseNotifyPropertyInfo where
type AttrAllowedOps TlsConnectionRequireCloseNotifyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsConnectionRequireCloseNotifyPropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionRequireCloseNotifyPropertyInfo = (~) Bool
type AttrTransferTypeConstraint TlsConnectionRequireCloseNotifyPropertyInfo = (~) Bool
type AttrTransferType TlsConnectionRequireCloseNotifyPropertyInfo = Bool
type AttrGetType TlsConnectionRequireCloseNotifyPropertyInfo = Bool
type AttrLabel TlsConnectionRequireCloseNotifyPropertyInfo = "require-close-notify"
type AttrOrigin TlsConnectionRequireCloseNotifyPropertyInfo = TlsConnection
attrGet = getTlsConnectionRequireCloseNotify
attrSet = setTlsConnectionRequireCloseNotify
attrTransfer _ v = do
return v
attrConstruct = constructTlsConnectionRequireCloseNotify
attrClear = undefined
#endif
getTlsConnectionUseSystemCertdb :: (MonadIO m, IsTlsConnection o) => o -> m Bool
getTlsConnectionUseSystemCertdb :: o -> m Bool
getTlsConnectionUseSystemCertdb 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-system-certdb"
setTlsConnectionUseSystemCertdb :: (MonadIO m, IsTlsConnection o) => o -> Bool -> m ()
setTlsConnectionUseSystemCertdb :: o -> Bool -> m ()
setTlsConnectionUseSystemCertdb 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-system-certdb" Bool
val
constructTlsConnectionUseSystemCertdb :: (IsTlsConnection o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTlsConnectionUseSystemCertdb :: Bool -> m (GValueConstruct o)
constructTlsConnectionUseSystemCertdb 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-system-certdb" Bool
val
#if defined(ENABLE_OVERLOADING)
data TlsConnectionUseSystemCertdbPropertyInfo
instance AttrInfo TlsConnectionUseSystemCertdbPropertyInfo where
type AttrAllowedOps TlsConnectionUseSystemCertdbPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsConnectionUseSystemCertdbPropertyInfo = IsTlsConnection
type AttrSetTypeConstraint TlsConnectionUseSystemCertdbPropertyInfo = (~) Bool
type AttrTransferTypeConstraint TlsConnectionUseSystemCertdbPropertyInfo = (~) Bool
type AttrTransferType TlsConnectionUseSystemCertdbPropertyInfo = Bool
type AttrGetType TlsConnectionUseSystemCertdbPropertyInfo = Bool
type AttrLabel TlsConnectionUseSystemCertdbPropertyInfo = "use-system-certdb"
type AttrOrigin TlsConnectionUseSystemCertdbPropertyInfo = TlsConnection
attrGet = getTlsConnectionUseSystemCertdb
attrSet = setTlsConnectionUseSystemCertdb
attrTransfer _ v = do
return v
attrConstruct = constructTlsConnectionUseSystemCertdb
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsConnection
type instance O.AttributeList TlsConnection = TlsConnectionAttributeList
type TlsConnectionAttributeList = ('[ '("advertisedProtocols", TlsConnectionAdvertisedProtocolsPropertyInfo), '("baseIoStream", TlsConnectionBaseIoStreamPropertyInfo), '("certificate", TlsConnectionCertificatePropertyInfo), '("closed", Gio.IOStream.IOStreamClosedPropertyInfo), '("database", TlsConnectionDatabasePropertyInfo), '("inputStream", Gio.IOStream.IOStreamInputStreamPropertyInfo), '("interaction", TlsConnectionInteractionPropertyInfo), '("negotiatedProtocol", TlsConnectionNegotiatedProtocolPropertyInfo), '("outputStream", Gio.IOStream.IOStreamOutputStreamPropertyInfo), '("peerCertificate", TlsConnectionPeerCertificatePropertyInfo), '("peerCertificateErrors", TlsConnectionPeerCertificateErrorsPropertyInfo), '("rehandshakeMode", TlsConnectionRehandshakeModePropertyInfo), '("requireCloseNotify", TlsConnectionRequireCloseNotifyPropertyInfo), '("useSystemCertdb", TlsConnectionUseSystemCertdbPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
tlsConnectionAdvertisedProtocols :: AttrLabelProxy "advertisedProtocols"
tlsConnectionAdvertisedProtocols = AttrLabelProxy
tlsConnectionBaseIoStream :: AttrLabelProxy "baseIoStream"
tlsConnectionBaseIoStream = AttrLabelProxy
tlsConnectionCertificate :: AttrLabelProxy "certificate"
tlsConnectionCertificate = AttrLabelProxy
tlsConnectionDatabase :: AttrLabelProxy "database"
tlsConnectionDatabase = AttrLabelProxy
tlsConnectionInteraction :: AttrLabelProxy "interaction"
tlsConnectionInteraction = AttrLabelProxy
tlsConnectionNegotiatedProtocol :: AttrLabelProxy "negotiatedProtocol"
tlsConnectionNegotiatedProtocol = AttrLabelProxy
tlsConnectionPeerCertificate :: AttrLabelProxy "peerCertificate"
tlsConnectionPeerCertificate = AttrLabelProxy
tlsConnectionPeerCertificateErrors :: AttrLabelProxy "peerCertificateErrors"
tlsConnectionPeerCertificateErrors = AttrLabelProxy
tlsConnectionRehandshakeMode :: AttrLabelProxy "rehandshakeMode"
tlsConnectionRehandshakeMode = AttrLabelProxy
tlsConnectionRequireCloseNotify :: AttrLabelProxy "requireCloseNotify"
tlsConnectionRequireCloseNotify = AttrLabelProxy
tlsConnectionUseSystemCertdb :: AttrLabelProxy "useSystemCertdb"
tlsConnectionUseSystemCertdb = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TlsConnection = TlsConnectionSignalList
type TlsConnectionSignalList = ('[ '("acceptCertificate", TlsConnectionAcceptCertificateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_tls_connection_emit_accept_certificate" g_tls_connection_emit_accept_certificate ::
Ptr TlsConnection ->
Ptr Gio.TlsCertificate.TlsCertificate ->
CUInt ->
IO CInt
tlsConnectionEmitAcceptCertificate ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) =>
a
-> b
-> [Gio.Flags.TlsCertificateFlags]
-> m Bool
tlsConnectionEmitAcceptCertificate :: a -> b -> [TlsCertificateFlags] -> m Bool
tlsConnectionEmitAcceptCertificate a
conn b
peerCert [TlsCertificateFlags]
errors = 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsCertificate
peerCert' <- b -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
peerCert
let errors' :: CUInt
errors' = [TlsCertificateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TlsCertificateFlags]
errors
CInt
result <- Ptr TlsConnection -> Ptr TlsCertificate -> CUInt -> IO CInt
g_tls_connection_emit_accept_certificate Ptr TlsConnection
conn' Ptr TlsCertificate
peerCert' CUInt
errors'
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
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
peerCert
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TlsConnectionEmitAcceptCertificateMethodInfo
instance (signature ~ (b -> [Gio.Flags.TlsCertificateFlags] -> m Bool), MonadIO m, IsTlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) => O.MethodInfo TlsConnectionEmitAcceptCertificateMethodInfo a signature where
overloadedMethod = tlsConnectionEmitAcceptCertificate
#endif
foreign import ccall "g_tls_connection_get_certificate" g_tls_connection_get_certificate ::
Ptr TlsConnection ->
IO (Ptr Gio.TlsCertificate.TlsCertificate)
tlsConnectionGetCertificate ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m Gio.TlsCertificate.TlsCertificate
tlsConnectionGetCertificate :: a -> m TlsCertificate
tlsConnectionGetCertificate a
conn = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsCertificate -> m TlsCertificate)
-> IO TlsCertificate -> m TlsCertificate
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsCertificate
result <- Ptr TlsConnection -> IO (Ptr TlsCertificate)
g_tls_connection_get_certificate Ptr TlsConnection
conn'
Text -> Ptr TlsCertificate -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsConnectionGetCertificate" Ptr TlsCertificate
result
TlsCertificate
result' <- ((ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TlsCertificate -> TlsCertificate
Gio.TlsCertificate.TlsCertificate) Ptr TlsCertificate
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result'
#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetCertificateMethodInfo
instance (signature ~ (m Gio.TlsCertificate.TlsCertificate), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetCertificateMethodInfo a signature where
overloadedMethod = tlsConnectionGetCertificate
#endif
foreign import ccall "g_tls_connection_get_database" g_tls_connection_get_database ::
Ptr TlsConnection ->
IO (Ptr Gio.TlsDatabase.TlsDatabase)
tlsConnectionGetDatabase ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m Gio.TlsDatabase.TlsDatabase
tlsConnectionGetDatabase :: a -> m TlsDatabase
tlsConnectionGetDatabase a
conn = IO TlsDatabase -> m TlsDatabase
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsDatabase -> m TlsDatabase)
-> IO TlsDatabase -> m TlsDatabase
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsDatabase
result <- Ptr TlsConnection -> IO (Ptr TlsDatabase)
g_tls_connection_get_database Ptr TlsConnection
conn'
Text -> Ptr TlsDatabase -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsConnectionGetDatabase" Ptr TlsDatabase
result
TlsDatabase
result' <- ((ManagedPtr TlsDatabase -> TlsDatabase)
-> Ptr TlsDatabase -> IO TlsDatabase
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TlsDatabase -> TlsDatabase
Gio.TlsDatabase.TlsDatabase) Ptr TlsDatabase
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
TlsDatabase -> IO TlsDatabase
forall (m :: * -> *) a. Monad m => a -> m a
return TlsDatabase
result'
#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetDatabaseMethodInfo
instance (signature ~ (m Gio.TlsDatabase.TlsDatabase), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetDatabaseMethodInfo a signature where
overloadedMethod = tlsConnectionGetDatabase
#endif
foreign import ccall "g_tls_connection_get_interaction" g_tls_connection_get_interaction ::
Ptr TlsConnection ->
IO (Ptr Gio.TlsInteraction.TlsInteraction)
tlsConnectionGetInteraction ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m Gio.TlsInteraction.TlsInteraction
tlsConnectionGetInteraction :: a -> m TlsInteraction
tlsConnectionGetInteraction a
conn = IO TlsInteraction -> m TlsInteraction
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsInteraction -> m TlsInteraction)
-> IO TlsInteraction -> m TlsInteraction
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsInteraction
result <- Ptr TlsConnection -> IO (Ptr TlsInteraction)
g_tls_connection_get_interaction Ptr TlsConnection
conn'
Text -> Ptr TlsInteraction -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsConnectionGetInteraction" Ptr TlsInteraction
result
TlsInteraction
result' <- ((ManagedPtr TlsInteraction -> TlsInteraction)
-> Ptr TlsInteraction -> IO TlsInteraction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TlsInteraction -> TlsInteraction
Gio.TlsInteraction.TlsInteraction) Ptr TlsInteraction
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
TlsInteraction -> IO TlsInteraction
forall (m :: * -> *) a. Monad m => a -> m a
return TlsInteraction
result'
#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetInteractionMethodInfo
instance (signature ~ (m Gio.TlsInteraction.TlsInteraction), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetInteractionMethodInfo a signature where
overloadedMethod = tlsConnectionGetInteraction
#endif
foreign import ccall "g_tls_connection_get_negotiated_protocol" g_tls_connection_get_negotiated_protocol ::
Ptr TlsConnection ->
IO CString
tlsConnectionGetNegotiatedProtocol ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m (Maybe T.Text)
tlsConnectionGetNegotiatedProtocol :: a -> m (Maybe Text)
tlsConnectionGetNegotiatedProtocol a
conn = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
CString
result <- Ptr TlsConnection -> IO CString
g_tls_connection_get_negotiated_protocol Ptr TlsConnection
conn'
Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetNegotiatedProtocolMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetNegotiatedProtocolMethodInfo a signature where
overloadedMethod = tlsConnectionGetNegotiatedProtocol
#endif
foreign import ccall "g_tls_connection_get_peer_certificate" g_tls_connection_get_peer_certificate ::
Ptr TlsConnection ->
IO (Ptr Gio.TlsCertificate.TlsCertificate)
tlsConnectionGetPeerCertificate ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m Gio.TlsCertificate.TlsCertificate
tlsConnectionGetPeerCertificate :: a -> m TlsCertificate
tlsConnectionGetPeerCertificate a
conn = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsCertificate -> m TlsCertificate)
-> IO TlsCertificate -> m TlsCertificate
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsCertificate
result <- Ptr TlsConnection -> IO (Ptr TlsCertificate)
g_tls_connection_get_peer_certificate Ptr TlsConnection
conn'
Text -> Ptr TlsCertificate -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsConnectionGetPeerCertificate" Ptr TlsCertificate
result
TlsCertificate
result' <- ((ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TlsCertificate -> TlsCertificate
Gio.TlsCertificate.TlsCertificate) Ptr TlsCertificate
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result'
#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetPeerCertificateMethodInfo
instance (signature ~ (m Gio.TlsCertificate.TlsCertificate), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetPeerCertificateMethodInfo a signature where
overloadedMethod = tlsConnectionGetPeerCertificate
#endif
foreign import ccall "g_tls_connection_get_peer_certificate_errors" g_tls_connection_get_peer_certificate_errors ::
Ptr TlsConnection ->
IO CUInt
tlsConnectionGetPeerCertificateErrors ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m [Gio.Flags.TlsCertificateFlags]
tlsConnectionGetPeerCertificateErrors :: a -> m [TlsCertificateFlags]
tlsConnectionGetPeerCertificateErrors 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
CUInt
result <- Ptr TlsConnection -> IO CUInt
g_tls_connection_get_peer_certificate_errors Ptr TlsConnection
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 TlsConnectionGetPeerCertificateErrorsMethodInfo
instance (signature ~ (m [Gio.Flags.TlsCertificateFlags]), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetPeerCertificateErrorsMethodInfo a signature where
overloadedMethod = tlsConnectionGetPeerCertificateErrors
#endif
foreign import ccall "g_tls_connection_get_rehandshake_mode" g_tls_connection_get_rehandshake_mode ::
Ptr TlsConnection ->
IO CUInt
{-# DEPRECATED tlsConnectionGetRehandshakeMode ["(Since version 2.60.)","Changing the rehandshake mode is no longer"," required for compatibility. Also, rehandshaking has been removed"," from the TLS protocol in TLS 1.3."] #-}
tlsConnectionGetRehandshakeMode ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m Gio.Enums.TlsRehandshakeMode
tlsConnectionGetRehandshakeMode :: a -> m TlsRehandshakeMode
tlsConnectionGetRehandshakeMode a
conn = IO TlsRehandshakeMode -> m TlsRehandshakeMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsRehandshakeMode -> m TlsRehandshakeMode)
-> IO TlsRehandshakeMode -> m TlsRehandshakeMode
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
CUInt
result <- Ptr TlsConnection -> IO CUInt
g_tls_connection_get_rehandshake_mode Ptr TlsConnection
conn'
let result' :: TlsRehandshakeMode
result' = (Int -> TlsRehandshakeMode
forall a. Enum a => Int -> a
toEnum (Int -> TlsRehandshakeMode)
-> (CUInt -> Int) -> CUInt -> TlsRehandshakeMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
TlsRehandshakeMode -> IO TlsRehandshakeMode
forall (m :: * -> *) a. Monad m => a -> m a
return TlsRehandshakeMode
result'
#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetRehandshakeModeMethodInfo
instance (signature ~ (m Gio.Enums.TlsRehandshakeMode), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetRehandshakeModeMethodInfo a signature where
overloadedMethod = tlsConnectionGetRehandshakeMode
#endif
foreign import ccall "g_tls_connection_get_require_close_notify" g_tls_connection_get_require_close_notify ::
Ptr TlsConnection ->
IO CInt
tlsConnectionGetRequireCloseNotify ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m Bool
tlsConnectionGetRequireCloseNotify :: a -> m Bool
tlsConnectionGetRequireCloseNotify 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
CInt
result <- Ptr TlsConnection -> IO CInt
g_tls_connection_get_require_close_notify Ptr TlsConnection
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 TlsConnectionGetRequireCloseNotifyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetRequireCloseNotifyMethodInfo a signature where
overloadedMethod = tlsConnectionGetRequireCloseNotify
#endif
foreign import ccall "g_tls_connection_get_use_system_certdb" g_tls_connection_get_use_system_certdb ::
Ptr TlsConnection ->
IO CInt
{-# DEPRECATED tlsConnectionGetUseSystemCertdb ["(Since version 2.30)","Use 'GI.Gio.Objects.TlsConnection.tlsConnectionGetDatabase' instead"] #-}
tlsConnectionGetUseSystemCertdb ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> m Bool
tlsConnectionGetUseSystemCertdb :: a -> m Bool
tlsConnectionGetUseSystemCertdb 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
CInt
result <- Ptr TlsConnection -> IO CInt
g_tls_connection_get_use_system_certdb Ptr TlsConnection
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 TlsConnectionGetUseSystemCertdbMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionGetUseSystemCertdbMethodInfo a signature where
overloadedMethod = tlsConnectionGetUseSystemCertdb
#endif
foreign import ccall "g_tls_connection_handshake" g_tls_connection_handshake ::
Ptr TlsConnection ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
tlsConnectionHandshake ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m ()
tlsConnectionHandshake :: a -> Maybe b -> m ()
tlsConnectionHandshake a
conn Maybe b
cancellable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
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 () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr TlsConnection -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_tls_connection_handshake Ptr TlsConnection
conn' Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data TlsConnectionHandshakeMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsTlsConnection a, Gio.Cancellable.IsCancellable b) => O.MethodInfo TlsConnectionHandshakeMethodInfo a signature where
overloadedMethod = tlsConnectionHandshake
#endif
foreign import ccall "g_tls_connection_handshake_async" g_tls_connection_handshake_async ::
Ptr TlsConnection ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
tlsConnectionHandshakeAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.Cancellable.IsCancellable b) =>
a
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
tlsConnectionHandshakeAsync :: a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
tlsConnectionHandshakeAsync a
conn Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
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'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr TlsConnection
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_tls_connection_handshake_async Ptr TlsConnection
conn' Int32
ioPriority Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsConnectionHandshakeAsyncMethodInfo
instance (signature ~ (Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsTlsConnection a, Gio.Cancellable.IsCancellable b) => O.MethodInfo TlsConnectionHandshakeAsyncMethodInfo a signature where
overloadedMethod = tlsConnectionHandshakeAsync
#endif
foreign import ccall "g_tls_connection_handshake_finish" g_tls_connection_handshake_finish ::
Ptr TlsConnection ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
tlsConnectionHandshakeFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
tlsConnectionHandshakeFinish :: a -> b -> m ()
tlsConnectionHandshakeFinish a
conn b
result_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr TlsConnection -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_tls_connection_handshake_finish Ptr TlsConnection
conn' Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data TlsConnectionHandshakeFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTlsConnection a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo TlsConnectionHandshakeFinishMethodInfo a signature where
overloadedMethod = tlsConnectionHandshakeFinish
#endif
foreign import ccall "g_tls_connection_set_advertised_protocols" g_tls_connection_set_advertised_protocols ::
Ptr TlsConnection ->
Ptr CString ->
IO ()
tlsConnectionSetAdvertisedProtocols ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> Maybe ([T.Text])
-> m ()
tlsConnectionSetAdvertisedProtocols :: a -> Maybe [Text] -> m ()
tlsConnectionSetAdvertisedProtocols a
conn Maybe [Text]
protocols = 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr CString
maybeProtocols <- case Maybe [Text]
protocols of
Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
Just [Text]
jProtocols -> do
Ptr CString
jProtocols' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jProtocols
Ptr CString -> IO (Ptr CString)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jProtocols'
Ptr TlsConnection -> Ptr CString -> IO ()
g_tls_connection_set_advertised_protocols Ptr TlsConnection
conn' Ptr CString
maybeProtocols
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeProtocols
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeProtocols
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsConnectionSetAdvertisedProtocolsMethodInfo
instance (signature ~ (Maybe ([T.Text]) -> m ()), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionSetAdvertisedProtocolsMethodInfo a signature where
overloadedMethod = tlsConnectionSetAdvertisedProtocols
#endif
foreign import ccall "g_tls_connection_set_certificate" g_tls_connection_set_certificate ::
Ptr TlsConnection ->
Ptr Gio.TlsCertificate.TlsCertificate ->
IO ()
tlsConnectionSetCertificate ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) =>
a
-> b
-> m ()
tlsConnectionSetCertificate :: a -> b -> m ()
tlsConnectionSetCertificate a
conn b
certificate = 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsCertificate
certificate' <- b -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
certificate
Ptr TlsConnection -> Ptr TlsCertificate -> IO ()
g_tls_connection_set_certificate Ptr TlsConnection
conn' Ptr TlsCertificate
certificate'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
certificate
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsConnectionSetCertificateMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) => O.MethodInfo TlsConnectionSetCertificateMethodInfo a signature where
overloadedMethod = tlsConnectionSetCertificate
#endif
foreign import ccall "g_tls_connection_set_database" g_tls_connection_set_database ::
Ptr TlsConnection ->
Ptr Gio.TlsDatabase.TlsDatabase ->
IO ()
tlsConnectionSetDatabase ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.TlsDatabase.IsTlsDatabase b) =>
a
-> b
-> m ()
tlsConnectionSetDatabase :: a -> b -> m ()
tlsConnectionSetDatabase a
conn b
database = 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsDatabase
database' <- b -> IO (Ptr TlsDatabase)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
database
Ptr TlsConnection -> Ptr TlsDatabase -> IO ()
g_tls_connection_set_database Ptr TlsConnection
conn' Ptr TlsDatabase
database'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
database
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsConnectionSetDatabaseMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTlsConnection a, Gio.TlsDatabase.IsTlsDatabase b) => O.MethodInfo TlsConnectionSetDatabaseMethodInfo a signature where
overloadedMethod = tlsConnectionSetDatabase
#endif
foreign import ccall "g_tls_connection_set_interaction" g_tls_connection_set_interaction ::
Ptr TlsConnection ->
Ptr Gio.TlsInteraction.TlsInteraction ->
IO ()
tlsConnectionSetInteraction ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.TlsInteraction.IsTlsInteraction b) =>
a
-> Maybe (b)
-> m ()
tlsConnectionSetInteraction :: a -> Maybe b -> m ()
tlsConnectionSetInteraction a
conn Maybe b
interaction = 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
Ptr TlsInteraction
maybeInteraction <- case Maybe b
interaction of
Maybe b
Nothing -> Ptr TlsInteraction -> IO (Ptr TlsInteraction)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsInteraction
forall a. Ptr a
nullPtr
Just b
jInteraction -> do
Ptr TlsInteraction
jInteraction' <- b -> IO (Ptr TlsInteraction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jInteraction
Ptr TlsInteraction -> IO (Ptr TlsInteraction)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsInteraction
jInteraction'
Ptr TlsConnection -> Ptr TlsInteraction -> IO ()
g_tls_connection_set_interaction Ptr TlsConnection
conn' Ptr TlsInteraction
maybeInteraction
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
interaction b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsConnectionSetInteractionMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsTlsConnection a, Gio.TlsInteraction.IsTlsInteraction b) => O.MethodInfo TlsConnectionSetInteractionMethodInfo a signature where
overloadedMethod = tlsConnectionSetInteraction
#endif
foreign import ccall "g_tls_connection_set_rehandshake_mode" g_tls_connection_set_rehandshake_mode ::
Ptr TlsConnection ->
CUInt ->
IO ()
{-# DEPRECATED tlsConnectionSetRehandshakeMode ["(Since version 2.60.)","Changing the rehandshake mode is no longer"," required for compatibility. Also, rehandshaking has been removed"," from the TLS protocol in TLS 1.3."] #-}
tlsConnectionSetRehandshakeMode ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> Gio.Enums.TlsRehandshakeMode
-> m ()
tlsConnectionSetRehandshakeMode :: a -> TlsRehandshakeMode -> m ()
tlsConnectionSetRehandshakeMode a
conn TlsRehandshakeMode
mode = 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let mode' :: CUInt
mode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TlsRehandshakeMode -> Int) -> TlsRehandshakeMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TlsRehandshakeMode -> Int
forall a. Enum a => a -> Int
fromEnum) TlsRehandshakeMode
mode
Ptr TlsConnection -> CUInt -> IO ()
g_tls_connection_set_rehandshake_mode Ptr TlsConnection
conn' CUInt
mode'
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 TlsConnectionSetRehandshakeModeMethodInfo
instance (signature ~ (Gio.Enums.TlsRehandshakeMode -> m ()), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionSetRehandshakeModeMethodInfo a signature where
overloadedMethod = tlsConnectionSetRehandshakeMode
#endif
foreign import ccall "g_tls_connection_set_require_close_notify" g_tls_connection_set_require_close_notify ::
Ptr TlsConnection ->
CInt ->
IO ()
tlsConnectionSetRequireCloseNotify ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> Bool
-> m ()
tlsConnectionSetRequireCloseNotify :: a -> Bool -> m ()
tlsConnectionSetRequireCloseNotify a
conn Bool
requireCloseNotify = 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let requireCloseNotify' :: CInt
requireCloseNotify' = (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
requireCloseNotify
Ptr TlsConnection -> CInt -> IO ()
g_tls_connection_set_require_close_notify Ptr TlsConnection
conn' CInt
requireCloseNotify'
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 TlsConnectionSetRequireCloseNotifyMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionSetRequireCloseNotifyMethodInfo a signature where
overloadedMethod = tlsConnectionSetRequireCloseNotify
#endif
foreign import ccall "g_tls_connection_set_use_system_certdb" g_tls_connection_set_use_system_certdb ::
Ptr TlsConnection ->
CInt ->
IO ()
{-# DEPRECATED tlsConnectionSetUseSystemCertdb ["(Since version 2.30)","Use 'GI.Gio.Objects.TlsConnection.tlsConnectionSetDatabase' instead"] #-}
tlsConnectionSetUseSystemCertdb ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
a
-> Bool
-> m ()
tlsConnectionSetUseSystemCertdb :: a -> Bool -> m ()
tlsConnectionSetUseSystemCertdb a
conn Bool
useSystemCertdb = 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 TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let useSystemCertdb' :: CInt
useSystemCertdb' = (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
useSystemCertdb
Ptr TlsConnection -> CInt -> IO ()
g_tls_connection_set_use_system_certdb Ptr TlsConnection
conn' CInt
useSystemCertdb'
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 TlsConnectionSetUseSystemCertdbMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTlsConnection a) => O.MethodInfo TlsConnectionSetUseSystemCertdbMethodInfo a signature where
overloadedMethod = tlsConnectionSetUseSystemCertdb
#endif