{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.TlsConnection.TlsConnection' is the base TLS connection class type, which wraps
-- a t'GI.Gio.Objects.IOStream.IOStream' and provides TLS encryption on top of it. Its
-- subclasses, t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection' and t'GI.Gio.Interfaces.TlsServerConnection.TlsServerConnection',
-- implement client-side and server-side TLS, respectively.
-- 
-- For DTLS (Datagram TLS) support, see t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'.
-- 
-- /Since: 2.28/

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gio.Objects.TlsConnection
    ( 

-- * Exported types
    TlsConnection(..)                       ,
    IsTlsConnection                         ,
    toTlsConnection                         ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clearPending]("GI.Gio.Objects.IOStream#g:method:clearPending"), [close]("GI.Gio.Objects.IOStream#g:method:close"), [closeAsync]("GI.Gio.Objects.IOStream#g:method:closeAsync"), [closeFinish]("GI.Gio.Objects.IOStream#g:method:closeFinish"), [emitAcceptCertificate]("GI.Gio.Objects.TlsConnection#g:method:emitAcceptCertificate"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [handshake]("GI.Gio.Objects.TlsConnection#g:method:handshake"), [handshakeAsync]("GI.Gio.Objects.TlsConnection#g:method:handshakeAsync"), [handshakeFinish]("GI.Gio.Objects.TlsConnection#g:method:handshakeFinish"), [hasPending]("GI.Gio.Objects.IOStream#g:method:hasPending"), [isClosed]("GI.Gio.Objects.IOStream#g:method:isClosed"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [spliceAsync]("GI.Gio.Objects.IOStream#g:method:spliceAsync"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCertificate]("GI.Gio.Objects.TlsConnection#g:method:getCertificate"), [getChannelBindingData]("GI.Gio.Objects.TlsConnection#g:method:getChannelBindingData"), [getCiphersuiteName]("GI.Gio.Objects.TlsConnection#g:method:getCiphersuiteName"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDatabase]("GI.Gio.Objects.TlsConnection#g:method:getDatabase"), [getInputStream]("GI.Gio.Objects.IOStream#g:method:getInputStream"), [getInteraction]("GI.Gio.Objects.TlsConnection#g:method:getInteraction"), [getNegotiatedProtocol]("GI.Gio.Objects.TlsConnection#g:method:getNegotiatedProtocol"), [getOutputStream]("GI.Gio.Objects.IOStream#g:method:getOutputStream"), [getPeerCertificate]("GI.Gio.Objects.TlsConnection#g:method:getPeerCertificate"), [getPeerCertificateErrors]("GI.Gio.Objects.TlsConnection#g:method:getPeerCertificateErrors"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getProtocolVersion]("GI.Gio.Objects.TlsConnection#g:method:getProtocolVersion"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRehandshakeMode]("GI.Gio.Objects.TlsConnection#g:method:getRehandshakeMode"), [getRequireCloseNotify]("GI.Gio.Objects.TlsConnection#g:method:getRequireCloseNotify"), [getUseSystemCertdb]("GI.Gio.Objects.TlsConnection#g:method:getUseSystemCertdb").
-- 
-- ==== Setters
-- [setAdvertisedProtocols]("GI.Gio.Objects.TlsConnection#g:method:setAdvertisedProtocols"), [setCertificate]("GI.Gio.Objects.TlsConnection#g:method:setCertificate"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDatabase]("GI.Gio.Objects.TlsConnection#g:method:setDatabase"), [setInteraction]("GI.Gio.Objects.TlsConnection#g:method:setInteraction"), [setPending]("GI.Gio.Objects.IOStream#g:method:setPending"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRehandshakeMode]("GI.Gio.Objects.TlsConnection#g:method:setRehandshakeMode"), [setRequireCloseNotify]("GI.Gio.Objects.TlsConnection#g:method:setRequireCloseNotify"), [setUseSystemCertdb]("GI.Gio.Objects.TlsConnection#g:method:setUseSystemCertdb").

#if defined(ENABLE_OVERLOADING)
    ResolveTlsConnectionMethod              ,
#endif

-- ** emitAcceptCertificate #method:emitAcceptCertificate#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionEmitAcceptCertificateMethodInfo,
#endif
    tlsConnectionEmitAcceptCertificate      ,


-- ** getCertificate #method:getCertificate#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetCertificateMethodInfo   ,
#endif
    tlsConnectionGetCertificate             ,


-- ** getChannelBindingData #method:getChannelBindingData#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetChannelBindingDataMethodInfo,
#endif
    tlsConnectionGetChannelBindingData      ,


-- ** getCiphersuiteName #method:getCiphersuiteName#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetCiphersuiteNameMethodInfo,
#endif
    tlsConnectionGetCiphersuiteName         ,


-- ** getDatabase #method:getDatabase#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetDatabaseMethodInfo      ,
#endif
    tlsConnectionGetDatabase                ,


-- ** getInteraction #method:getInteraction#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetInteractionMethodInfo   ,
#endif
    tlsConnectionGetInteraction             ,


-- ** getNegotiatedProtocol #method:getNegotiatedProtocol#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetNegotiatedProtocolMethodInfo,
#endif
    tlsConnectionGetNegotiatedProtocol      ,


-- ** getPeerCertificate #method:getPeerCertificate#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetPeerCertificateMethodInfo,
#endif
    tlsConnectionGetPeerCertificate         ,


-- ** getPeerCertificateErrors #method:getPeerCertificateErrors#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetPeerCertificateErrorsMethodInfo,
#endif
    tlsConnectionGetPeerCertificateErrors   ,


-- ** getProtocolVersion #method:getProtocolVersion#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetProtocolVersionMethodInfo,
#endif
    tlsConnectionGetProtocolVersion         ,


-- ** getRehandshakeMode #method:getRehandshakeMode#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetRehandshakeModeMethodInfo,
#endif
    tlsConnectionGetRehandshakeMode         ,


-- ** getRequireCloseNotify #method:getRequireCloseNotify#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetRequireCloseNotifyMethodInfo,
#endif
    tlsConnectionGetRequireCloseNotify      ,


-- ** getUseSystemCertdb #method:getUseSystemCertdb#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionGetUseSystemCertdbMethodInfo,
#endif
    tlsConnectionGetUseSystemCertdb         ,


-- ** handshake #method:handshake#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionHandshakeMethodInfo        ,
#endif
    tlsConnectionHandshake                  ,


-- ** handshakeAsync #method:handshakeAsync#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionHandshakeAsyncMethodInfo   ,
#endif
    tlsConnectionHandshakeAsync             ,


-- ** handshakeFinish #method:handshakeFinish#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionHandshakeFinishMethodInfo  ,
#endif
    tlsConnectionHandshakeFinish            ,


-- ** setAdvertisedProtocols #method:setAdvertisedProtocols#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionSetAdvertisedProtocolsMethodInfo,
#endif
    tlsConnectionSetAdvertisedProtocols     ,


-- ** setCertificate #method:setCertificate#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionSetCertificateMethodInfo   ,
#endif
    tlsConnectionSetCertificate             ,


-- ** setDatabase #method:setDatabase#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionSetDatabaseMethodInfo      ,
#endif
    tlsConnectionSetDatabase                ,


-- ** setInteraction #method:setInteraction#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionSetInteractionMethodInfo   ,
#endif
    tlsConnectionSetInteraction             ,


-- ** setRehandshakeMode #method:setRehandshakeMode#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionSetRehandshakeModeMethodInfo,
#endif
    tlsConnectionSetRehandshakeMode         ,


-- ** setRequireCloseNotify #method:setRequireCloseNotify#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionSetRequireCloseNotifyMethodInfo,
#endif
    tlsConnectionSetRequireCloseNotify      ,


-- ** setUseSystemCertdb #method:setUseSystemCertdb#

#if defined(ENABLE_OVERLOADING)
    TlsConnectionSetUseSystemCertdbMethodInfo,
#endif
    tlsConnectionSetUseSystemCertdb         ,




 -- * Properties


-- ** advertisedProtocols #attr:advertisedProtocols#
-- | The list of application-layer protocols that the connection
-- advertises that it is willing to speak. See
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionSetAdvertisedProtocols'.
-- 
-- /Since: 2.60/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionAdvertisedProtocolsPropertyInfo,
#endif
    clearTlsConnectionAdvertisedProtocols   ,
    constructTlsConnectionAdvertisedProtocols,
    getTlsConnectionAdvertisedProtocols     ,
    setTlsConnectionAdvertisedProtocols     ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionAdvertisedProtocols        ,
#endif


-- ** baseIoStream #attr:baseIoStream#
-- | The t'GI.Gio.Objects.IOStream.IOStream' that the connection wraps. The connection holds a reference
-- to this stream, and may run operations on the stream from other threads
-- throughout its lifetime. Consequently, after the t'GI.Gio.Objects.IOStream.IOStream' has been
-- constructed, application code may only run its own operations on this
-- stream when no t'GI.Gio.Objects.IOStream.IOStream' operations are running.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionBaseIoStreamPropertyInfo   ,
#endif
    constructTlsConnectionBaseIoStream      ,
    getTlsConnectionBaseIoStream            ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionBaseIoStream               ,
#endif


-- ** certificate #attr:certificate#
-- | The connection\'s certificate; see
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionSetCertificate'.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionCertificatePropertyInfo    ,
#endif
    constructTlsConnectionCertificate       ,
    getTlsConnectionCertificate             ,
    setTlsConnectionCertificate             ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionCertificate                ,
#endif


-- ** ciphersuiteName #attr:ciphersuiteName#
-- | The name of the TLS ciphersuite in use. See 'GI.Gio.Objects.TlsConnection.tlsConnectionGetCiphersuiteName'.
-- 
-- /Since: 2.70/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionCiphersuiteNamePropertyInfo,
#endif
    getTlsConnectionCiphersuiteName         ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionCiphersuiteName            ,
#endif


-- ** database #attr:database#
-- | The certificate database to use when verifying this TLS connection.
-- If no certificate database is set, then the default database will be
-- used. See 'GI.Gio.Interfaces.TlsBackend.tlsBackendGetDefaultDatabase'.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionDatabasePropertyInfo       ,
#endif
    clearTlsConnectionDatabase              ,
    constructTlsConnectionDatabase          ,
    getTlsConnectionDatabase                ,
    setTlsConnectionDatabase                ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionDatabase                   ,
#endif


-- ** interaction #attr:interaction#
-- | A t'GI.Gio.Objects.TlsInteraction.TlsInteraction' object to be used when the connection or certificate
-- database need to interact with the user. This will be used to prompt the
-- user for passwords where necessary.
-- 
-- /Since: 2.30/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionInteractionPropertyInfo    ,
#endif
    clearTlsConnectionInteraction           ,
    constructTlsConnectionInteraction       ,
    getTlsConnectionInteraction             ,
    setTlsConnectionInteraction             ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionInteraction                ,
#endif


-- ** negotiatedProtocol #attr:negotiatedProtocol#
-- | The application-layer protocol negotiated during the TLS
-- handshake. See 'GI.Gio.Objects.TlsConnection.tlsConnectionGetNegotiatedProtocol'.
-- 
-- /Since: 2.60/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionNegotiatedProtocolPropertyInfo,
#endif
    getTlsConnectionNegotiatedProtocol      ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionNegotiatedProtocol         ,
#endif


-- ** peerCertificate #attr:peerCertificate#
-- | The connection\'s peer\'s certificate, after the TLS handshake has
-- completed or failed. Note in particular that this is not yet set
-- during the emission of [TlsConnection::acceptCertificate]("GI.Gio.Objects.TlsConnection#g:signal:acceptCertificate").
-- 
-- (You can watch for a [Object::notify]("GI.GObject.Objects.Object#g:signal:notify") signal on this property to
-- detect when a handshake has occurred.)
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionPeerCertificatePropertyInfo,
#endif
    getTlsConnectionPeerCertificate         ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionPeerCertificate            ,
#endif


-- ** peerCertificateErrors #attr:peerCertificateErrors#
-- | The errors noticed while verifying
-- [TlsConnection:peerCertificate]("GI.Gio.Objects.TlsConnection#g:attr:peerCertificate"). Normally this should be 0, but
-- it may not be if t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection':@/validation-flags/@ is not
-- 'GI.Gio.Flags.TlsCertificateFlagsValidateAll', or if
-- [TlsConnection::acceptCertificate]("GI.Gio.Objects.TlsConnection#g:signal:acceptCertificate") overrode the default
-- behavior.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionPeerCertificateErrorsPropertyInfo,
#endif
    getTlsConnectionPeerCertificateErrors   ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionPeerCertificateErrors      ,
#endif


-- ** protocolVersion #attr:protocolVersion#
-- | The TLS protocol version in use. See 'GI.Gio.Objects.TlsConnection.tlsConnectionGetProtocolVersion'.
-- 
-- /Since: 2.70/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionProtocolVersionPropertyInfo,
#endif
    getTlsConnectionProtocolVersion         ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionProtocolVersion            ,
#endif


-- ** rehandshakeMode #attr:rehandshakeMode#
-- | The rehandshaking mode. See
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionSetRehandshakeMode'.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionRehandshakeModePropertyInfo,
#endif
    constructTlsConnectionRehandshakeMode   ,
    getTlsConnectionRehandshakeMode         ,
    setTlsConnectionRehandshakeMode         ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionRehandshakeMode            ,
#endif


-- ** requireCloseNotify #attr:requireCloseNotify#
-- | Whether or not proper TLS close notification is required.
-- See 'GI.Gio.Objects.TlsConnection.tlsConnectionSetRequireCloseNotify'.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsConnectionRequireCloseNotifyPropertyInfo,
#endif
    constructTlsConnectionRequireCloseNotify,
    getTlsConnectionRequireCloseNotify      ,
    setTlsConnectionRequireCloseNotify      ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionRequireCloseNotify         ,
#endif


-- ** useSystemCertdb #attr:useSystemCertdb#
-- | Whether or not the system certificate database will be used to
-- verify peer certificates. See
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionSetUseSystemCertdb'.

#if defined(ENABLE_OVERLOADING)
    TlsConnectionUseSystemCertdbPropertyInfo,
#endif
    constructTlsConnectionUseSystemCertdb   ,
    getTlsConnectionUseSystemCertdb         ,
    setTlsConnectionUseSystemCertdb         ,
#if defined(ENABLE_OVERLOADING)
    tlsConnectionUseSystemCertdb            ,
#endif




 -- * Signals


-- ** acceptCertificate #signal:acceptCertificate#

    TlsConnectionAcceptCertificateCallback  ,
#if defined(ENABLE_OVERLOADING)
    TlsConnectionAcceptCertificateSignalInfo,
#endif
    afterTlsConnectionAcceptCertificate     ,
    onTlsConnectionAcceptCertificate        ,




    ) 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.GArray as B.GArray
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.Coerce as Coerce
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 GHC.Records as R

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

-- | Memory-managed wrapper type.
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

-- | Type class for types which can be safely cast to `TlsConnection`, for instance with `toTlsConnection`.
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]

-- | Cast to `TlsConnection`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toTlsConnection :: (MIO.MonadIO m, IsTlsConnection o) => o -> m TlsConnection
toTlsConnection :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m TlsConnection
toTlsConnection = IO TlsConnection -> m TlsConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr TlsConnection -> TlsConnection
TlsConnection

-- | Convert 'TlsConnection' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe TlsConnection) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_tls_connection_get_type
    gvalueSet_ :: Ptr GValue -> Maybe TlsConnection -> IO ()
gvalueSet_ Ptr GValue
gv Maybe TlsConnection
P.Nothing = Ptr GValue -> Ptr TlsConnection -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr TlsConnection
forall a. Ptr a
FP.nullPtr :: FP.Ptr TlsConnection)
    gvalueSet_ Ptr GValue
gv (P.Just TlsConnection
obj) = TlsConnection -> (Ptr TlsConnection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsConnection
obj (Ptr GValue -> Ptr TlsConnection -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe TlsConnection)
gvalueGet_ Ptr GValue
gv = do
        Ptr TlsConnection
ptr <- Ptr GValue -> IO (Ptr TlsConnection)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr TlsConnection)
        if Ptr TlsConnection
ptr Ptr TlsConnection -> Ptr TlsConnection -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TlsConnection
forall a. Ptr a
FP.nullPtr
        then TlsConnection -> Maybe TlsConnection
forall a. a -> Maybe a
P.Just (TlsConnection -> Maybe TlsConnection)
-> IO TlsConnection -> IO (Maybe TlsConnection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe TlsConnection -> IO (Maybe TlsConnection)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsConnection
forall a. Maybe a
P.Nothing
        
    

#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 "getChannelBindingData" o = TlsConnectionGetChannelBindingDataMethodInfo
    ResolveTlsConnectionMethod "getCiphersuiteName" o = TlsConnectionGetCiphersuiteNameMethodInfo
    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 "getProtocolVersion" o = TlsConnectionGetProtocolVersionMethodInfo
    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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTlsConnectionMethod t TlsConnection, O.OverloadedMethod info TlsConnection p, R.HasField t TlsConnection p) => R.HasField t TlsConnection p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveTlsConnectionMethod t TlsConnection, O.OverloadedMethodInfo info TlsConnection) => OL.IsLabel t (O.MethodProxy info TlsConnection) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- signal TlsConnection::accept-certificate
-- | Emitted during the TLS handshake after the peer certificate has
-- been received. You can examine /@peerCert@/\'s certification path by
-- calling 'GI.Gio.Objects.TlsCertificate.tlsCertificateGetIssuer' on it.
-- 
-- For a client-side connection, /@peerCert@/ is the server\'s
-- certificate, and the signal will only be emitted if the
-- certificate was not acceptable according to /@conn@/\'s
-- t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection':@/validation_flags/@. If you would like the
-- certificate to be accepted despite /@errors@/, return 'P.True' from the
-- signal handler. Otherwise, if no handler accepts the certificate,
-- the handshake will fail with 'GI.Gio.Enums.TlsErrorBadCertificate'.
-- 
-- For a server-side connection, /@peerCert@/ is the certificate
-- presented by the client, if this was requested via the server\'s
-- t'GI.Gio.Interfaces.TlsServerConnection.TlsServerConnection':@/authentication_mode/@. On the server side,
-- the signal is always emitted when the client presents a
-- certificate, and the certificate will only be accepted if a
-- handler returns 'P.True'.
-- 
-- Note that if this signal is emitted as part of asynchronous I\/O
-- in the main thread, then you should not attempt to interact with
-- the user before returning from the signal handler. If you want to
-- let the user decide whether or not to accept the certificate, you
-- would have to return 'P.False' from the signal handler on the first
-- attempt, and then after the connection attempt returns a
-- 'GI.Gio.Enums.TlsErrorBadCertificate', you can interact with the user, and
-- if the user decides to accept the certificate, remember that fact,
-- create a new connection, and return 'P.True' from the signal handler
-- the next time.
-- 
-- If you are doing I\/O in another thread, you do not
-- need to worry about this, and can simply block in the signal
-- handler until the UI thread returns an answer.
-- 
-- /Since: 2.28/
type TlsConnectionAcceptCertificateCallback =
    Gio.TlsCertificate.TlsCertificate
    -- ^ /@peerCert@/: the peer\'s t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> [Gio.Flags.TlsCertificateFlags]
    -- ^ /@errors@/: the problems with /@peerCert@/.
    -> IO Bool
    -- ^ __Returns:__ 'P.True' to accept /@peerCert@/ (which will also
    -- immediately end the signal emission). 'P.False' to allow the signal
    -- emission to continue, which will cause the handshake to fail if
    -- no one else overrides it.

type C_TlsConnectionAcceptCertificateCallback =
    Ptr TlsConnection ->                    -- object
    Ptr Gio.TlsCertificate.TlsCertificate ->
    CUInt ->
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_TlsConnectionAcceptCertificateCallback`.
foreign import ccall "wrapper"
    mk_TlsConnectionAcceptCertificateCallback :: C_TlsConnectionAcceptCertificateCallback -> IO (FunPtr C_TlsConnectionAcceptCertificateCallback)

wrap_TlsConnectionAcceptCertificateCallback :: 
    GObject a => (a -> TlsConnectionAcceptCertificateCallback) ->
    C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback :: forall a.
GObject a =>
(a -> TlsConnectionAcceptCertificateCallback)
-> C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback a -> TlsConnectionAcceptCertificateCallback
gi'cb Ptr TlsConnection
gi'selfPtr 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 <- Ptr TlsConnection -> (TlsConnection -> IO Bool) -> IO Bool
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr TlsConnection
gi'selfPtr ((TlsConnection -> IO Bool) -> IO Bool)
-> (TlsConnection -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \TlsConnection
gi'self -> a -> TlsConnectionAcceptCertificateCallback
gi'cb (TlsConnection -> a
Coerce.coerce TlsConnection
gi'self)  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'


-- | Connect a signal handler for the [acceptCertificate](#signal:acceptCertificate) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' tlsConnection #acceptCertificate callback
-- @
-- 
-- 
onTlsConnectionAcceptCertificate :: (IsTlsConnection a, MonadIO m) => a -> ((?self :: a) => TlsConnectionAcceptCertificateCallback) -> m SignalHandlerId
onTlsConnectionAcceptCertificate :: forall a (m :: * -> *).
(IsTlsConnection a, MonadIO m) =>
a
-> ((?self::a) => TlsConnectionAcceptCertificateCallback)
-> m SignalHandlerId
onTlsConnectionAcceptCertificate a
obj (?self::a) => 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 wrapped :: a -> TlsConnectionAcceptCertificateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => TlsConnectionAcceptCertificateCallback
TlsConnectionAcceptCertificateCallback
cb
    let wrapped' :: C_TlsConnectionAcceptCertificateCallback
wrapped' = (a -> TlsConnectionAcceptCertificateCallback)
-> C_TlsConnectionAcceptCertificateCallback
forall a.
GObject a =>
(a -> TlsConnectionAcceptCertificateCallback)
-> C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback a -> TlsConnectionAcceptCertificateCallback
wrapped
    FunPtr C_TlsConnectionAcceptCertificateCallback
wrapped'' <- C_TlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_TlsConnectionAcceptCertificateCallback)
mk_TlsConnectionAcceptCertificateCallback C_TlsConnectionAcceptCertificateCallback
wrapped'
    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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [acceptCertificate](#signal:acceptCertificate) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' tlsConnection #acceptCertificate callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTlsConnectionAcceptCertificate :: (IsTlsConnection a, MonadIO m) => a -> ((?self :: a) => TlsConnectionAcceptCertificateCallback) -> m SignalHandlerId
afterTlsConnectionAcceptCertificate :: forall a (m :: * -> *).
(IsTlsConnection a, MonadIO m) =>
a
-> ((?self::a) => TlsConnectionAcceptCertificateCallback)
-> m SignalHandlerId
afterTlsConnectionAcceptCertificate a
obj (?self::a) => 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 wrapped :: a -> TlsConnectionAcceptCertificateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => TlsConnectionAcceptCertificateCallback
TlsConnectionAcceptCertificateCallback
cb
    let wrapped' :: C_TlsConnectionAcceptCertificateCallback
wrapped' = (a -> TlsConnectionAcceptCertificateCallback)
-> C_TlsConnectionAcceptCertificateCallback
forall a.
GObject a =>
(a -> TlsConnectionAcceptCertificateCallback)
-> C_TlsConnectionAcceptCertificateCallback
wrap_TlsConnectionAcceptCertificateCallback a -> TlsConnectionAcceptCertificateCallback
wrapped
    FunPtr C_TlsConnectionAcceptCertificateCallback
wrapped'' <- C_TlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_TlsConnectionAcceptCertificateCallback)
mk_TlsConnectionAcceptCertificateCallback C_TlsConnectionAcceptCertificateCallback
wrapped'
    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
wrapped'' 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
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection::accept-certificate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:signal:acceptCertificate"})

#endif

-- VVV Prop "advertised-protocols"
   -- Type: TCArray True (-1) (-1) (TBasicType TUTF8)
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just True)

-- | Get the value of the “@advertised-protocols@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #advertisedProtocols
-- @
getTlsConnectionAdvertisedProtocols :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe [T.Text])
getTlsConnectionAdvertisedProtocols :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m (Maybe [Text])
getTlsConnectionAdvertisedProtocols o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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"

-- | Set the value of the “@advertised-protocols@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsConnection [ #advertisedProtocols 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsConnectionAdvertisedProtocols :: (MonadIO m, IsTlsConnection o) => o -> [T.Text] -> m ()
setTlsConnectionAdvertisedProtocols :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> [Text] -> m ()
setTlsConnectionAdvertisedProtocols o
obj [Text]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    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)

-- | Construct a `GValueConstruct` with valid value for the “@advertised-protocols@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsConnectionAdvertisedProtocols :: (IsTlsConnection o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructTlsConnectionAdvertisedProtocols :: forall o (m :: * -> *).
(IsTlsConnection o, MonadIO m) =>
[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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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)

-- | Set the value of the “@advertised-protocols@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #advertisedProtocols
-- @
clearTlsConnectionAdvertisedProtocols :: (MonadIO m, IsTlsConnection o) => o -> m ()
clearTlsConnectionAdvertisedProtocols :: forall (m :: * -> *) o. (MonadIO m, IsTlsConnection o) => 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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.advertisedProtocols"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:advertisedProtocols"
        })
#endif

-- VVV Prop "base-io-stream"
   -- Type: TInterface (Name {namespace = "Gio", name = "IOStream"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@base-io-stream@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #baseIoStream
-- @
getTlsConnectionBaseIoStream :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe Gio.IOStream.IOStream)
getTlsConnectionBaseIoStream :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m (Maybe IOStream)
getTlsConnectionBaseIoStream o
obj = IO (Maybe IOStream) -> m (Maybe IOStream)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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

-- | Construct a `GValueConstruct` with valid value for the “@base-io-stream@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsConnectionBaseIoStream :: (IsTlsConnection o, MIO.MonadIO m, Gio.IOStream.IsIOStream a) => a -> m (GValueConstruct o)
constructTlsConnectionBaseIoStream :: forall o (m :: * -> *) a.
(IsTlsConnection o, MonadIO m, IsIOStream a) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.baseIoStream"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:baseIoStream"
        })
#endif

-- VVV Prop "certificate"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just False)

-- | Get the value of the “@certificate@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #certificate
-- @
getTlsConnectionCertificate :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe Gio.TlsCertificate.TlsCertificate)
getTlsConnectionCertificate :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m (Maybe TlsCertificate)
getTlsConnectionCertificate o
obj = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate))
-> IO (Maybe TlsCertificate) -> m (Maybe 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

-- | Set the value of the “@certificate@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsConnection [ #certificate 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsConnectionCertificate :: (MonadIO m, IsTlsConnection o, Gio.TlsCertificate.IsTlsCertificate a) => o -> a -> m ()
setTlsConnectionCertificate :: forall (m :: * -> *) o a.
(MonadIO m, IsTlsConnection o, IsTlsCertificate a) =>
o -> a -> m ()
setTlsConnectionCertificate o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    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)

-- | Construct a `GValueConstruct` with valid value for the “@certificate@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsConnectionCertificate :: (IsTlsConnection o, MIO.MonadIO m, Gio.TlsCertificate.IsTlsCertificate a) => a -> m (GValueConstruct o)
constructTlsConnectionCertificate :: forall o (m :: * -> *) a.
(IsTlsConnection o, MonadIO m, IsTlsCertificate a) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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 = (Maybe 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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.certificate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:certificate"
        })
#endif

-- VVV Prop "ciphersuite-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@ciphersuite-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #ciphersuiteName
-- @
getTlsConnectionCiphersuiteName :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe T.Text)
getTlsConnectionCiphersuiteName :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m (Maybe Text)
getTlsConnectionCiphersuiteName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"ciphersuite-name"

#if defined(ENABLE_OVERLOADING)
data TlsConnectionCiphersuiteNamePropertyInfo
instance AttrInfo TlsConnectionCiphersuiteNamePropertyInfo where
    type AttrAllowedOps TlsConnectionCiphersuiteNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsConnectionCiphersuiteNamePropertyInfo = IsTlsConnection
    type AttrSetTypeConstraint TlsConnectionCiphersuiteNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsConnectionCiphersuiteNamePropertyInfo = (~) ()
    type AttrTransferType TlsConnectionCiphersuiteNamePropertyInfo = ()
    type AttrGetType TlsConnectionCiphersuiteNamePropertyInfo = (Maybe T.Text)
    type AttrLabel TlsConnectionCiphersuiteNamePropertyInfo = "ciphersuite-name"
    type AttrOrigin TlsConnectionCiphersuiteNamePropertyInfo = TlsConnection
    attrGet = getTlsConnectionCiphersuiteName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.ciphersuiteName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:ciphersuiteName"
        })
#endif

-- VVV Prop "database"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsDatabase"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@database@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #database
-- @
getTlsConnectionDatabase :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe Gio.TlsDatabase.TlsDatabase)
getTlsConnectionDatabase :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m (Maybe TlsDatabase)
getTlsConnectionDatabase o
obj = IO (Maybe TlsDatabase) -> m (Maybe TlsDatabase)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TlsDatabase) -> m (Maybe TlsDatabase))
-> IO (Maybe TlsDatabase) -> m (Maybe 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

-- | Set the value of the “@database@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsConnection [ #database 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsConnectionDatabase :: (MonadIO m, IsTlsConnection o, Gio.TlsDatabase.IsTlsDatabase a) => o -> a -> m ()
setTlsConnectionDatabase :: forall (m :: * -> *) o a.
(MonadIO m, IsTlsConnection o, IsTlsDatabase a) =>
o -> a -> m ()
setTlsConnectionDatabase o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    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)

-- | Construct a `GValueConstruct` with valid value for the “@database@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsConnectionDatabase :: (IsTlsConnection o, MIO.MonadIO m, Gio.TlsDatabase.IsTlsDatabase a) => a -> m (GValueConstruct o)
constructTlsConnectionDatabase :: forall o (m :: * -> *) a.
(IsTlsConnection o, MonadIO m, IsTlsDatabase a) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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)

-- | Set the value of the “@database@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #database
-- @
clearTlsConnectionDatabase :: (MonadIO m, IsTlsConnection o) => o -> m ()
clearTlsConnectionDatabase :: forall (m :: * -> *) o. (MonadIO m, IsTlsConnection o) => o -> m ()
clearTlsConnectionDatabase 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 TlsDatabase -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"database" (Maybe TlsDatabase
forall a. Maybe a
Nothing :: Maybe Gio.TlsDatabase.TlsDatabase)

#if defined(ENABLE_OVERLOADING)
data TlsConnectionDatabasePropertyInfo
instance AttrInfo TlsConnectionDatabasePropertyInfo where
    type AttrAllowedOps TlsConnectionDatabasePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    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 = (Maybe 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 = clearTlsConnectionDatabase
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.database"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:database"
        })
#endif

-- VVV Prop "interaction"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsInteraction"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@interaction@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #interaction
-- @
getTlsConnectionInteraction :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe Gio.TlsInteraction.TlsInteraction)
getTlsConnectionInteraction :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m (Maybe TlsInteraction)
getTlsConnectionInteraction o
obj = IO (Maybe TlsInteraction) -> m (Maybe TlsInteraction)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TlsInteraction) -> m (Maybe TlsInteraction))
-> IO (Maybe TlsInteraction) -> m (Maybe 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

-- | Set the value of the “@interaction@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsConnection [ #interaction 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsConnectionInteraction :: (MonadIO m, IsTlsConnection o, Gio.TlsInteraction.IsTlsInteraction a) => o -> a -> m ()
setTlsConnectionInteraction :: forall (m :: * -> *) o a.
(MonadIO m, IsTlsConnection o, IsTlsInteraction a) =>
o -> a -> m ()
setTlsConnectionInteraction o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    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)

-- | Construct a `GValueConstruct` with valid value for the “@interaction@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsConnectionInteraction :: (IsTlsConnection o, MIO.MonadIO m, Gio.TlsInteraction.IsTlsInteraction a) => a -> m (GValueConstruct o)
constructTlsConnectionInteraction :: forall o (m :: * -> *) a.
(IsTlsConnection o, MonadIO m, IsTlsInteraction a) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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)

-- | Set the value of the “@interaction@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #interaction
-- @
clearTlsConnectionInteraction :: (MonadIO m, IsTlsConnection o) => o -> m ()
clearTlsConnectionInteraction :: forall (m :: * -> *) o. (MonadIO m, IsTlsConnection o) => 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 = (Maybe 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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.interaction"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:interaction"
        })
#endif

-- VVV Prop "negotiated-protocol"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@negotiated-protocol@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #negotiatedProtocol
-- @
getTlsConnectionNegotiatedProtocol :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe T.Text)
getTlsConnectionNegotiatedProtocol :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m (Maybe Text)
getTlsConnectionNegotiatedProtocol o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.negotiatedProtocol"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:negotiatedProtocol"
        })
#endif

-- VVV Prop "peer-certificate"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@peer-certificate@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #peerCertificate
-- @
getTlsConnectionPeerCertificate :: (MonadIO m, IsTlsConnection o) => o -> m (Maybe Gio.TlsCertificate.TlsCertificate)
getTlsConnectionPeerCertificate :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m (Maybe TlsCertificate)
getTlsConnectionPeerCertificate o
obj = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate))
-> IO (Maybe TlsCertificate) -> m (Maybe 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 = (Maybe Gio.TlsCertificate.TlsCertificate)
    type AttrLabel TlsConnectionPeerCertificatePropertyInfo = "peer-certificate"
    type AttrOrigin TlsConnectionPeerCertificatePropertyInfo = TlsConnection
    attrGet = getTlsConnectionPeerCertificate
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.peerCertificate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:peerCertificate"
        })
#endif

-- VVV Prop "peer-certificate-errors"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsCertificateFlags"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@peer-certificate-errors@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #peerCertificateErrors
-- @
getTlsConnectionPeerCertificateErrors :: (MonadIO m, IsTlsConnection o) => o -> m [Gio.Flags.TlsCertificateFlags]
getTlsConnectionPeerCertificateErrors :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m [TlsCertificateFlags]
getTlsConnectionPeerCertificateErrors o
obj = IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.peerCertificateErrors"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:peerCertificateErrors"
        })
#endif

-- VVV Prop "protocol-version"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsProtocolVersion"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@protocol-version@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #protocolVersion
-- @
getTlsConnectionProtocolVersion :: (MonadIO m, IsTlsConnection o) => o -> m Gio.Enums.TlsProtocolVersion
getTlsConnectionProtocolVersion :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m TlsProtocolVersion
getTlsConnectionProtocolVersion o
obj = IO TlsProtocolVersion -> m TlsProtocolVersion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO TlsProtocolVersion -> m TlsProtocolVersion)
-> IO TlsProtocolVersion -> m TlsProtocolVersion
forall a b. (a -> b) -> a -> b
$ o -> String -> IO TlsProtocolVersion
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"protocol-version"

#if defined(ENABLE_OVERLOADING)
data TlsConnectionProtocolVersionPropertyInfo
instance AttrInfo TlsConnectionProtocolVersionPropertyInfo where
    type AttrAllowedOps TlsConnectionProtocolVersionPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint TlsConnectionProtocolVersionPropertyInfo = IsTlsConnection
    type AttrSetTypeConstraint TlsConnectionProtocolVersionPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsConnectionProtocolVersionPropertyInfo = (~) ()
    type AttrTransferType TlsConnectionProtocolVersionPropertyInfo = ()
    type AttrGetType TlsConnectionProtocolVersionPropertyInfo = Gio.Enums.TlsProtocolVersion
    type AttrLabel TlsConnectionProtocolVersionPropertyInfo = "protocol-version"
    type AttrOrigin TlsConnectionProtocolVersionPropertyInfo = TlsConnection
    attrGet = getTlsConnectionProtocolVersion
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.protocolVersion"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:protocolVersion"
        })
#endif

-- VVV Prop "rehandshake-mode"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsRehandshakeMode"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@rehandshake-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #rehandshakeMode
-- @
getTlsConnectionRehandshakeMode :: (MonadIO m, IsTlsConnection o) => o -> m Gio.Enums.TlsRehandshakeMode
getTlsConnectionRehandshakeMode :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m TlsRehandshakeMode
getTlsConnectionRehandshakeMode o
obj = IO TlsRehandshakeMode -> m TlsRehandshakeMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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"

-- | Set the value of the “@rehandshake-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsConnection [ #rehandshakeMode 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsConnectionRehandshakeMode :: (MonadIO m, IsTlsConnection o) => o -> Gio.Enums.TlsRehandshakeMode -> m ()
setTlsConnectionRehandshakeMode :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> TlsRehandshakeMode -> m ()
setTlsConnectionRehandshakeMode o
obj TlsRehandshakeMode
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    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

-- | Construct a `GValueConstruct` with valid value for the “@rehandshake-mode@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsConnectionRehandshakeMode :: (IsTlsConnection o, MIO.MonadIO m) => Gio.Enums.TlsRehandshakeMode -> m (GValueConstruct o)
constructTlsConnectionRehandshakeMode :: forall o (m :: * -> *).
(IsTlsConnection o, MonadIO m) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.rehandshakeMode"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:rehandshakeMode"
        })
#endif

-- VVV Prop "require-close-notify"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@require-close-notify@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #requireCloseNotify
-- @
getTlsConnectionRequireCloseNotify :: (MonadIO m, IsTlsConnection o) => o -> m Bool
getTlsConnectionRequireCloseNotify :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m Bool
getTlsConnectionRequireCloseNotify o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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"

-- | Set the value of the “@require-close-notify@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsConnection [ #requireCloseNotify 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsConnectionRequireCloseNotify :: (MonadIO m, IsTlsConnection o) => o -> Bool -> m ()
setTlsConnectionRequireCloseNotify :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> Bool -> m ()
setTlsConnectionRequireCloseNotify o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"require-close-notify" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@require-close-notify@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsConnectionRequireCloseNotify :: (IsTlsConnection o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTlsConnectionRequireCloseNotify :: forall o (m :: * -> *).
(IsTlsConnection o, MonadIO m) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.requireCloseNotify"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:requireCloseNotify"
        })
#endif

-- VVV Prop "use-system-certdb"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@use-system-certdb@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsConnection #useSystemCertdb
-- @
getTlsConnectionUseSystemCertdb :: (MonadIO m, IsTlsConnection o) => o -> m Bool
getTlsConnectionUseSystemCertdb :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> m Bool
getTlsConnectionUseSystemCertdb o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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"

-- | Set the value of the “@use-system-certdb@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsConnection [ #useSystemCertdb 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsConnectionUseSystemCertdb :: (MonadIO m, IsTlsConnection o) => o -> Bool -> m ()
setTlsConnectionUseSystemCertdb :: forall (m :: * -> *) o.
(MonadIO m, IsTlsConnection o) =>
o -> Bool -> m ()
setTlsConnectionUseSystemCertdb o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-system-certdb" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@use-system-certdb@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsConnectionUseSystemCertdb :: (IsTlsConnection o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTlsConnectionUseSystemCertdb :: forall o (m :: * -> *).
(IsTlsConnection o, MonadIO m) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.useSystemCertdb"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#g:attr:useSystemCertdb"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsConnection
type instance O.AttributeList TlsConnection = TlsConnectionAttributeList
type TlsConnectionAttributeList = ('[ '("advertisedProtocols", TlsConnectionAdvertisedProtocolsPropertyInfo), '("baseIoStream", TlsConnectionBaseIoStreamPropertyInfo), '("certificate", TlsConnectionCertificatePropertyInfo), '("ciphersuiteName", TlsConnectionCiphersuiteNamePropertyInfo), '("closed", Gio.IOStream.IOStreamClosedPropertyInfo), '("database", TlsConnectionDatabasePropertyInfo), '("inputStream", Gio.IOStream.IOStreamInputStreamPropertyInfo), '("interaction", TlsConnectionInteractionPropertyInfo), '("negotiatedProtocol", TlsConnectionNegotiatedProtocolPropertyInfo), '("outputStream", Gio.IOStream.IOStreamOutputStreamPropertyInfo), '("peerCertificate", TlsConnectionPeerCertificatePropertyInfo), '("peerCertificateErrors", TlsConnectionPeerCertificateErrorsPropertyInfo), '("protocolVersion", TlsConnectionProtocolVersionPropertyInfo), '("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

tlsConnectionCiphersuiteName :: AttrLabelProxy "ciphersuiteName"
tlsConnectionCiphersuiteName = 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

tlsConnectionProtocolVersion :: AttrLabelProxy "protocolVersion"
tlsConnectionProtocolVersion = 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

-- method TlsConnection::emit_accept_certificate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "peer_cert"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the peer's #GTlsCertificate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "errors"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsCertificateFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the problems with @peer_cert"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_emit_accept_certificate" g_tls_connection_emit_accept_certificate :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    Ptr Gio.TlsCertificate.TlsCertificate -> -- peer_cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    CUInt ->                                -- errors : TInterface (Name {namespace = "Gio", name = "TlsCertificateFlags"})
    IO CInt

-- | Used by t'GI.Gio.Objects.TlsConnection.TlsConnection' implementations to emit the
-- [TlsConnection::acceptCertificate]("GI.Gio.Objects.TlsConnection#g:signal:acceptCertificate") signal.
-- 
-- /Since: 2.28/
tlsConnectionEmitAcceptCertificate ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> b
    -- ^ /@peerCert@/: the peer\'s t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> [Gio.Flags.TlsCertificateFlags]
    -- ^ /@errors@/: the problems with /@peerCert@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' if one of the signal handlers has returned
    --     'P.True' to accept /@peerCert@/
tlsConnectionEmitAcceptCertificate :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTlsConnection a, IsTlsCertificate b) =>
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.OverloadedMethod TlsConnectionEmitAcceptCertificateMethodInfo a signature where
    overloadedMethod = tlsConnectionEmitAcceptCertificate

instance O.OverloadedMethodInfo TlsConnectionEmitAcceptCertificateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionEmitAcceptCertificate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionEmitAcceptCertificate"
        })


#endif

-- method TlsConnection::get_certificate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "TlsCertificate" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_certificate" g_tls_connection_get_certificate :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO (Ptr Gio.TlsCertificate.TlsCertificate)

-- | Gets /@conn@/\'s certificate, as set by
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionSetCertificate'.
-- 
-- /Since: 2.28/
tlsConnectionGetCertificate ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m (Maybe Gio.TlsCertificate.TlsCertificate)
    -- ^ __Returns:__ /@conn@/\'s certificate, or 'P.Nothing'
tlsConnectionGetCertificate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
a -> m (Maybe TlsCertificate)
tlsConnectionGetCertificate a
conn = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate))
-> IO (Maybe TlsCertificate) -> m (Maybe 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'
    Maybe TlsCertificate
maybeResult <- Ptr TlsCertificate
-> (Ptr TlsCertificate -> IO TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TlsCertificate
result ((Ptr TlsCertificate -> IO TlsCertificate)
 -> IO (Maybe TlsCertificate))
-> (Ptr TlsCertificate -> IO TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b. (a -> b) -> a -> b
$ \Ptr TlsCertificate
result' -> do
        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'
        TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    Maybe TlsCertificate -> IO (Maybe TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsCertificate
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetCertificateMethodInfo
instance (signature ~ (m (Maybe Gio.TlsCertificate.TlsCertificate)), MonadIO m, IsTlsConnection a) => O.OverloadedMethod TlsConnectionGetCertificateMethodInfo a signature where
    overloadedMethod = tlsConnectionGetCertificate

instance O.OverloadedMethodInfo TlsConnectionGetCertificateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetCertificate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetCertificate"
        })


#endif

-- method TlsConnection::get_channel_binding_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsChannelBindingType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GTlsChannelBindingType type of data to fetch"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TByteArray
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "#GByteArray is\n       filled with the binding data, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_connection_get_channel_binding_data" g_tls_connection_get_channel_binding_data :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    CUInt ->                                -- type : TInterface (Name {namespace = "Gio", name = "TlsChannelBindingType"})
    Ptr (Ptr GByteArray) ->                 -- data : TByteArray
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Query the TLS backend for TLS channel binding data of /@type@/ for /@conn@/.
-- 
-- This call retrieves TLS channel binding data as specified in RFC
-- <https://tools.ietf.org/html/rfc5056 5056>, RFC
-- <https://tools.ietf.org/html/rfc5929 5929>, and related RFCs.  The
-- binding data is returned in /@data@/.  The /@data@/ is resized by the callee
-- using t'GI.GLib.Structs.ByteArray.ByteArray' buffer management and will be freed when the /@data@/
-- is destroyed by 'GI.GLib.Functions.byteArrayUnref'. If /@data@/ is 'P.Nothing', it will only
-- check whether TLS backend is able to fetch the data (e.g. whether /@type@/
-- is supported by the TLS backend). It does not guarantee that the data
-- will be available though.  That could happen if TLS connection does not
-- support /@type@/ or the binding data is not available yet due to additional
-- negotiation or input required.
-- 
-- /Since: 2.66/
tlsConnectionGetChannelBindingData ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> Gio.Enums.TlsChannelBindingType
    -- ^ /@type@/: t'GI.Gio.Enums.TlsChannelBindingType' type of data to fetch
    -> m (ByteString)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
tlsConnectionGetChannelBindingData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
a -> TlsChannelBindingType -> m ByteString
tlsConnectionGetChannelBindingData a
conn TlsChannelBindingType
type_ = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsConnection
conn' <- a -> IO (Ptr TlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TlsChannelBindingType -> Int) -> TlsChannelBindingType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TlsChannelBindingType -> Int
forall a. Enum a => a -> Int
fromEnum) TlsChannelBindingType
type_
    Ptr (Ptr GByteArray)
data_ <- IO (Ptr (Ptr GByteArray))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr GByteArray))
    IO ByteString -> IO () -> IO ByteString
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
-> CUInt -> Ptr (Ptr GByteArray) -> Ptr (Ptr GError) -> IO CInt
g_tls_connection_get_channel_binding_data Ptr TlsConnection
conn' CUInt
type_' Ptr (Ptr GByteArray)
data_
        Ptr GByteArray
data_' <- Ptr (Ptr GByteArray) -> IO (Ptr GByteArray)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr GByteArray)
data_
        ByteString
data_'' <- Ptr GByteArray -> IO ByteString
unpackGByteArray Ptr GByteArray
data_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
        Ptr (Ptr GByteArray) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr GByteArray)
data_
        ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
data_''
     ) (do
        Ptr (Ptr GByteArray) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr GByteArray)
data_
     )

#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetChannelBindingDataMethodInfo
instance (signature ~ (Gio.Enums.TlsChannelBindingType -> m (ByteString)), MonadIO m, IsTlsConnection a) => O.OverloadedMethod TlsConnectionGetChannelBindingDataMethodInfo a signature where
    overloadedMethod = tlsConnectionGetChannelBindingData

instance O.OverloadedMethodInfo TlsConnectionGetChannelBindingDataMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetChannelBindingData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetChannelBindingData"
        })


#endif

-- method TlsConnection::get_ciphersuite_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_ciphersuite_name" g_tls_connection_get_ciphersuite_name :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO CString

-- | Returns the name of the current TLS ciphersuite, or 'P.Nothing' if the
-- connection has not handshaked or has been closed. Beware that the TLS
-- backend may use any of multiple different naming conventions, because
-- OpenSSL and GnuTLS have their own ciphersuite naming conventions that
-- are different from each other and different from the standard, IANA-
-- registered ciphersuite names. The ciphersuite name is intended to be
-- displayed to the user for informative purposes only, and parsing it
-- is not recommended.
-- 
-- /Since: 2.70/
tlsConnectionGetCiphersuiteName ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The name of the current TLS ciphersuite, or 'P.Nothing'
tlsConnectionGetCiphersuiteName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
a -> m (Maybe Text)
tlsConnectionGetCiphersuiteName 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_ciphersuite_name 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'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem 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 TlsConnectionGetCiphersuiteNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsTlsConnection a) => O.OverloadedMethod TlsConnectionGetCiphersuiteNameMethodInfo a signature where
    overloadedMethod = tlsConnectionGetCiphersuiteName

instance O.OverloadedMethodInfo TlsConnectionGetCiphersuiteNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetCiphersuiteName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetCiphersuiteName"
        })


#endif

-- method TlsConnection::get_database
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "TlsDatabase" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_database" g_tls_connection_get_database :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO (Ptr Gio.TlsDatabase.TlsDatabase)

-- | Gets the certificate database that /@conn@/ uses to verify
-- peer certificates. See 'GI.Gio.Objects.TlsConnection.tlsConnectionSetDatabase'.
-- 
-- /Since: 2.30/
tlsConnectionGetDatabase ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m (Maybe Gio.TlsDatabase.TlsDatabase)
    -- ^ __Returns:__ the certificate database that /@conn@/ uses or 'P.Nothing'
tlsConnectionGetDatabase :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
a -> m (Maybe TlsDatabase)
tlsConnectionGetDatabase a
conn = IO (Maybe TlsDatabase) -> m (Maybe TlsDatabase)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TlsDatabase) -> m (Maybe TlsDatabase))
-> IO (Maybe TlsDatabase) -> m (Maybe 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'
    Maybe TlsDatabase
maybeResult <- Ptr TlsDatabase
-> (Ptr TlsDatabase -> IO TlsDatabase) -> IO (Maybe TlsDatabase)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TlsDatabase
result ((Ptr TlsDatabase -> IO TlsDatabase) -> IO (Maybe TlsDatabase))
-> (Ptr TlsDatabase -> IO TlsDatabase) -> IO (Maybe TlsDatabase)
forall a b. (a -> b) -> a -> b
$ \Ptr TlsDatabase
result' -> do
        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'
        TlsDatabase -> IO TlsDatabase
forall (m :: * -> *) a. Monad m => a -> m a
return TlsDatabase
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    Maybe TlsDatabase -> IO (Maybe TlsDatabase)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsDatabase
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetDatabaseMethodInfo
instance (signature ~ (m (Maybe Gio.TlsDatabase.TlsDatabase)), MonadIO m, IsTlsConnection a) => O.OverloadedMethod TlsConnectionGetDatabaseMethodInfo a signature where
    overloadedMethod = tlsConnectionGetDatabase

instance O.OverloadedMethodInfo TlsConnectionGetDatabaseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetDatabase",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetDatabase"
        })


#endif

-- method TlsConnection::get_interaction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a connection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "TlsInteraction" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_interaction" g_tls_connection_get_interaction :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO (Ptr Gio.TlsInteraction.TlsInteraction)

-- | Get the object that will be used to interact with the user. It will be used
-- for things like prompting the user for passwords. If 'P.Nothing' is returned, then
-- no user interaction will occur for this connection.
-- 
-- /Since: 2.30/
tlsConnectionGetInteraction ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a connection
    -> m (Maybe Gio.TlsInteraction.TlsInteraction)
    -- ^ __Returns:__ The interaction object.
tlsConnectionGetInteraction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
a -> m (Maybe TlsInteraction)
tlsConnectionGetInteraction a
conn = IO (Maybe TlsInteraction) -> m (Maybe TlsInteraction)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TlsInteraction) -> m (Maybe TlsInteraction))
-> IO (Maybe TlsInteraction) -> m (Maybe 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'
    Maybe TlsInteraction
maybeResult <- Ptr TlsInteraction
-> (Ptr TlsInteraction -> IO TlsInteraction)
-> IO (Maybe TlsInteraction)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TlsInteraction
result ((Ptr TlsInteraction -> IO TlsInteraction)
 -> IO (Maybe TlsInteraction))
-> (Ptr TlsInteraction -> IO TlsInteraction)
-> IO (Maybe TlsInteraction)
forall a b. (a -> b) -> a -> b
$ \Ptr TlsInteraction
result' -> do
        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'
        TlsInteraction -> IO TlsInteraction
forall (m :: * -> *) a. Monad m => a -> m a
return TlsInteraction
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    Maybe TlsInteraction -> IO (Maybe TlsInteraction)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsInteraction
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetInteractionMethodInfo
instance (signature ~ (m (Maybe Gio.TlsInteraction.TlsInteraction)), MonadIO m, IsTlsConnection a) => O.OverloadedMethod TlsConnectionGetInteractionMethodInfo a signature where
    overloadedMethod = tlsConnectionGetInteraction

instance O.OverloadedMethodInfo TlsConnectionGetInteractionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetInteraction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetInteraction"
        })


#endif

-- method TlsConnection::get_negotiated_protocol
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_negotiated_protocol" g_tls_connection_get_negotiated_protocol :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO CString

-- | Gets the name of the application-layer protocol negotiated during
-- the handshake.
-- 
-- If the peer did not use the ALPN extension, or did not advertise a
-- protocol that matched one of /@conn@/\'s protocols, or the TLS backend
-- does not support ALPN, then this will be 'P.Nothing'. See
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionSetAdvertisedProtocols'.
-- 
-- /Since: 2.60/
tlsConnectionGetNegotiatedProtocol ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the negotiated protocol, or 'P.Nothing'
tlsConnectionGetNegotiatedProtocol :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionGetNegotiatedProtocolMethodInfo a signature where
    overloadedMethod = tlsConnectionGetNegotiatedProtocol

instance O.OverloadedMethodInfo TlsConnectionGetNegotiatedProtocolMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetNegotiatedProtocol",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetNegotiatedProtocol"
        })


#endif

-- method TlsConnection::get_peer_certificate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "TlsCertificate" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_peer_certificate" g_tls_connection_get_peer_certificate :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO (Ptr Gio.TlsCertificate.TlsCertificate)

-- | Gets /@conn@/\'s peer\'s certificate after the handshake has completed
-- or failed. (It is not set during the emission of
-- [TlsConnection::acceptCertificate]("GI.Gio.Objects.TlsConnection#g:signal:acceptCertificate").)
-- 
-- /Since: 2.28/
tlsConnectionGetPeerCertificate ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m (Maybe Gio.TlsCertificate.TlsCertificate)
    -- ^ __Returns:__ /@conn@/\'s peer\'s certificate, or 'P.Nothing'
tlsConnectionGetPeerCertificate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
a -> m (Maybe TlsCertificate)
tlsConnectionGetPeerCertificate a
conn = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate))
-> IO (Maybe TlsCertificate) -> m (Maybe 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'
    Maybe TlsCertificate
maybeResult <- Ptr TlsCertificate
-> (Ptr TlsCertificate -> IO TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TlsCertificate
result ((Ptr TlsCertificate -> IO TlsCertificate)
 -> IO (Maybe TlsCertificate))
-> (Ptr TlsCertificate -> IO TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b. (a -> b) -> a -> b
$ \Ptr TlsCertificate
result' -> do
        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'
        TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    Maybe TlsCertificate -> IO (Maybe TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsCertificate
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetPeerCertificateMethodInfo
instance (signature ~ (m (Maybe Gio.TlsCertificate.TlsCertificate)), MonadIO m, IsTlsConnection a) => O.OverloadedMethod TlsConnectionGetPeerCertificateMethodInfo a signature where
    overloadedMethod = tlsConnectionGetPeerCertificate

instance O.OverloadedMethodInfo TlsConnectionGetPeerCertificateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetPeerCertificate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetPeerCertificate"
        })


#endif

-- method TlsConnection::get_peer_certificate_errors
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "TlsCertificateFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_peer_certificate_errors" g_tls_connection_get_peer_certificate_errors :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO CUInt

-- | Gets the errors associated with validating /@conn@/\'s peer\'s
-- certificate, after the handshake has completed or failed. (It is
-- not set during the emission of [TlsConnection::acceptCertificate]("GI.Gio.Objects.TlsConnection#g:signal:acceptCertificate").)
-- 
-- /Since: 2.28/
tlsConnectionGetPeerCertificateErrors ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m [Gio.Flags.TlsCertificateFlags]
    -- ^ __Returns:__ /@conn@/\'s peer\'s certificate errors
tlsConnectionGetPeerCertificateErrors :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionGetPeerCertificateErrorsMethodInfo a signature where
    overloadedMethod = tlsConnectionGetPeerCertificateErrors

instance O.OverloadedMethodInfo TlsConnectionGetPeerCertificateErrorsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetPeerCertificateErrors",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetPeerCertificateErrors"
        })


#endif

-- method TlsConnection::get_protocol_version
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "TlsProtocolVersion" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_protocol_version" g_tls_connection_get_protocol_version :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO CUInt

-- | Returns the current TLS protocol version, which may be
-- 'GI.Gio.Enums.TlsProtocolVersionUnknown' if the connection has not handshaked, or
-- has been closed, or if the TLS backend has implemented a protocol version
-- that is not a recognized t'GI.Gio.Enums.TlsProtocolVersion'.
-- 
-- /Since: 2.70/
tlsConnectionGetProtocolVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m Gio.Enums.TlsProtocolVersion
    -- ^ __Returns:__ The current TLS protocol version
tlsConnectionGetProtocolVersion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
a -> m TlsProtocolVersion
tlsConnectionGetProtocolVersion a
conn = IO TlsProtocolVersion -> m TlsProtocolVersion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsProtocolVersion -> m TlsProtocolVersion)
-> IO TlsProtocolVersion -> m TlsProtocolVersion
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_protocol_version Ptr TlsConnection
conn'
    let result' :: TlsProtocolVersion
result' = (Int -> TlsProtocolVersion
forall a. Enum a => Int -> a
toEnum (Int -> TlsProtocolVersion)
-> (CUInt -> Int) -> CUInt -> TlsProtocolVersion
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
    TlsProtocolVersion -> IO TlsProtocolVersion
forall (m :: * -> *) a. Monad m => a -> m a
return TlsProtocolVersion
result'

#if defined(ENABLE_OVERLOADING)
data TlsConnectionGetProtocolVersionMethodInfo
instance (signature ~ (m Gio.Enums.TlsProtocolVersion), MonadIO m, IsTlsConnection a) => O.OverloadedMethod TlsConnectionGetProtocolVersionMethodInfo a signature where
    overloadedMethod = tlsConnectionGetProtocolVersion

instance O.OverloadedMethodInfo TlsConnectionGetProtocolVersionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetProtocolVersion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetProtocolVersion"
        })


#endif

-- method TlsConnection::get_rehandshake_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "TlsRehandshakeMode" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_rehandshake_mode" g_tls_connection_get_rehandshake_mode :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "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."] #-}
-- | Gets /@conn@/ rehandshaking mode. See
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionSetRehandshakeMode' for details.
-- 
-- /Since: 2.28/
tlsConnectionGetRehandshakeMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m Gio.Enums.TlsRehandshakeMode
    -- ^ __Returns:__ 'GI.Gio.Enums.TlsRehandshakeModeSafely'
tlsConnectionGetRehandshakeMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionGetRehandshakeModeMethodInfo a signature where
    overloadedMethod = tlsConnectionGetRehandshakeMode

instance O.OverloadedMethodInfo TlsConnectionGetRehandshakeModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetRehandshakeMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetRehandshakeMode"
        })


#endif

-- method TlsConnection::get_require_close_notify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_require_close_notify" g_tls_connection_get_require_close_notify :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO CInt

-- | Tests whether or not /@conn@/ expects a proper TLS close notification
-- when the connection is closed. See
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionSetRequireCloseNotify' for details.
-- 
-- /Since: 2.28/
tlsConnectionGetRequireCloseNotify ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@conn@/ requires a proper TLS close
    -- notification.
tlsConnectionGetRequireCloseNotify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionGetRequireCloseNotifyMethodInfo a signature where
    overloadedMethod = tlsConnectionGetRequireCloseNotify

instance O.OverloadedMethodInfo TlsConnectionGetRequireCloseNotifyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetRequireCloseNotify",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetRequireCloseNotify"
        })


#endif

-- method TlsConnection::get_use_system_certdb
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_get_use_system_certdb" g_tls_connection_get_use_system_certdb :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    IO CInt

{-# DEPRECATED tlsConnectionGetUseSystemCertdb ["(Since version 2.30)","Use 'GI.Gio.Objects.TlsConnection.tlsConnectionGetDatabase' instead"] #-}
-- | Gets whether /@conn@/ uses the system certificate database to verify
-- peer certificates. See 'GI.Gio.Objects.TlsConnection.tlsConnectionSetUseSystemCertdb'.
tlsConnectionGetUseSystemCertdb ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> m Bool
    -- ^ __Returns:__ whether /@conn@/ uses the system certificate database
tlsConnectionGetUseSystemCertdb :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionGetUseSystemCertdbMethodInfo a signature where
    overloadedMethod = tlsConnectionGetUseSystemCertdb

instance O.OverloadedMethodInfo TlsConnectionGetUseSystemCertdbMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionGetUseSystemCertdb",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionGetUseSystemCertdb"
        })


#endif

-- method TlsConnection::handshake
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_connection_handshake" g_tls_connection_handshake :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Attempts a TLS handshake on /@conn@/.
-- 
-- On the client side, it is never necessary to call this method;
-- although the connection needs to perform a handshake after
-- connecting (or after sending a \"STARTTLS\"-type command),
-- t'GI.Gio.Objects.TlsConnection.TlsConnection' will handle this for you automatically when you try
-- to send or receive data on the connection. You can call
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionHandshake' manually if you want to know whether
-- the initial handshake succeeded or failed (as opposed to just
-- immediately trying to use /@conn@/ to read or write, in which case,
-- if it fails, it may not be possible to tell if it failed before or
-- after completing the handshake), but beware that servers may reject
-- client authentication after the handshake has completed, so a
-- successful handshake does not indicate the connection will be usable.
-- 
-- Likewise, on the server side, although a handshake is necessary at
-- the beginning of the communication, you do not need to call this
-- function explicitly unless you want clearer error reporting.
-- 
-- Previously, calling 'GI.Gio.Objects.TlsConnection.tlsConnectionHandshake' after the initial
-- handshake would trigger a rehandshake; however, this usage was
-- deprecated in GLib 2.60 because rehandshaking was removed from the
-- TLS protocol in TLS 1.3. Since GLib 2.64, calling this function after
-- the initial handshake will no longer do anything.
-- 
-- When using a t'GI.Gio.Objects.TlsConnection.TlsConnection' created by t'GI.Gio.Objects.SocketClient.SocketClient', the
-- t'GI.Gio.Objects.SocketClient.SocketClient' performs the initial handshake, so calling this
-- function manually is not recommended.
-- 
-- t'GI.Gio.Objects.TlsConnection.TlsConnection'::@/accept_certificate/@ may be emitted during the
-- handshake.
-- 
-- /Since: 2.28/
tlsConnectionHandshake ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
tlsConnectionHandshake :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTlsConnection a, IsCancellable b) =>
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.OverloadedMethod TlsConnectionHandshakeMethodInfo a signature where
    overloadedMethod = tlsConnectionHandshake

instance O.OverloadedMethodInfo TlsConnectionHandshakeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionHandshake",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionHandshake"
        })


#endif

-- method TlsConnection::handshake_async
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "io_priority"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the [I/O priority][io-priority] of the request"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "callback to call when the handshake is complete"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 4
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to the callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_handshake_async" g_tls_connection_handshake_async :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    Int32 ->                                -- io_priority : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously performs a TLS handshake on /@conn@/. See
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionHandshake' for more information.
-- 
-- /Since: 2.28/
tlsConnectionHandshakeAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> Int32
    -- ^ /@ioPriority@/: the [I\/O priority][io-priority] of the request
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: callback to call when the handshake is complete
    -> m ()
tlsConnectionHandshakeAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTlsConnection a, IsCancellable b) =>
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.OverloadedMethod TlsConnectionHandshakeAsyncMethodInfo a signature where
    overloadedMethod = tlsConnectionHandshakeAsync

instance O.OverloadedMethodInfo TlsConnectionHandshakeAsyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionHandshakeAsync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionHandshakeAsync"
        })


#endif

-- method TlsConnection::handshake_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncResult." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_connection_handshake_finish" g_tls_connection_handshake_finish :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finish an asynchronous TLS handshake operation. See
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionHandshake' for more information.
-- 
-- /Since: 2.28/
tlsConnectionHandshakeFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
tlsConnectionHandshakeFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTlsConnection a, IsAsyncResult b) =>
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.OverloadedMethod TlsConnectionHandshakeFinishMethodInfo a signature where
    overloadedMethod = tlsConnectionHandshakeFinish

instance O.OverloadedMethodInfo TlsConnectionHandshakeFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionHandshakeFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionHandshakeFinish"
        })


#endif

-- method TlsConnection::set_advertised_protocols
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "protocols"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a %NULL-terminated\n  array of ALPN protocol names (eg, \"http/1.1\", \"h2\"), or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_set_advertised_protocols" g_tls_connection_set_advertised_protocols :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    Ptr CString ->                          -- protocols : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO ()

-- | Sets the list of application-layer protocols to advertise that the
-- caller is willing to speak on this connection. The
-- Application-Layer Protocol Negotiation (ALPN) extension will be
-- used to negotiate a compatible protocol with the peer; use
-- 'GI.Gio.Objects.TlsConnection.tlsConnectionGetNegotiatedProtocol' to find the negotiated
-- protocol after the handshake.  Specifying 'P.Nothing' for the the value
-- of /@protocols@/ will disable ALPN negotiation.
-- 
-- See <https://www.iana.org/assignments/tls-extensiontype-values/tls-extensiontype-values.xhtml#alpn-protocol-ids IANA TLS ALPN Protocol IDs>
-- for a list of registered protocol IDs.
-- 
-- /Since: 2.60/
tlsConnectionSetAdvertisedProtocols ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> Maybe ([T.Text])
    -- ^ /@protocols@/: a 'P.Nothing'-terminated
    --   array of ALPN protocol names (eg, \"http\/1.1\", \"h2\"), or 'P.Nothing'
    -> m ()
tlsConnectionSetAdvertisedProtocols :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionSetAdvertisedProtocolsMethodInfo a signature where
    overloadedMethod = tlsConnectionSetAdvertisedProtocols

instance O.OverloadedMethodInfo TlsConnectionSetAdvertisedProtocolsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionSetAdvertisedProtocols",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionSetAdvertisedProtocols"
        })


#endif

-- method TlsConnection::set_certificate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "certificate"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the certificate to use for @conn"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_set_certificate" g_tls_connection_set_certificate :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    Ptr Gio.TlsCertificate.TlsCertificate -> -- certificate : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO ()

-- | This sets the certificate that /@conn@/ will present to its peer
-- during the TLS handshake. For a t'GI.Gio.Interfaces.TlsServerConnection.TlsServerConnection', it is
-- mandatory to set this, and that will normally be done at construct
-- time.
-- 
-- For a t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection', this is optional. If a handshake fails
-- with 'GI.Gio.Enums.TlsErrorCertificateRequired', that means that the server
-- requires a certificate, and if you try connecting again, you should
-- call this method first. You can call
-- 'GI.Gio.Interfaces.TlsClientConnection.tlsClientConnectionGetAcceptedCas' on the failed connection
-- to get a list of Certificate Authorities that the server will
-- accept certificates from.
-- 
-- (It is also possible that a server will allow the connection with
-- or without a certificate; in that case, if you don\'t provide a
-- certificate, you can tell that the server requested one by the fact
-- that 'GI.Gio.Interfaces.TlsClientConnection.tlsClientConnectionGetAcceptedCas' will return
-- non-'P.Nothing'.)
-- 
-- /Since: 2.28/
tlsConnectionSetCertificate ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> b
    -- ^ /@certificate@/: the certificate to use for /@conn@/
    -> m ()
tlsConnectionSetCertificate :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTlsConnection a, IsTlsCertificate b) =>
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.OverloadedMethod TlsConnectionSetCertificateMethodInfo a signature where
    overloadedMethod = tlsConnectionSetCertificate

instance O.OverloadedMethodInfo TlsConnectionSetCertificateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionSetCertificate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionSetCertificate"
        })


#endif

-- method TlsConnection::set_database
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "database"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsDatabase" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsDatabase" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_set_database" g_tls_connection_set_database :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    Ptr Gio.TlsDatabase.TlsDatabase ->      -- database : TInterface (Name {namespace = "Gio", name = "TlsDatabase"})
    IO ()

-- | Sets the certificate database that is used to verify peer certificates.
-- This is set to the default database by default. See
-- 'GI.Gio.Interfaces.TlsBackend.tlsBackendGetDefaultDatabase'. If set to 'P.Nothing', then
-- peer certificate validation will always set the
-- 'GI.Gio.Flags.TlsCertificateFlagsUnknownCa' error (meaning
-- [TlsConnection::acceptCertificate]("GI.Gio.Objects.TlsConnection#g:signal:acceptCertificate") will always be emitted on
-- client-side connections, unless that bit is not set in
-- t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection':@/validation-flags/@).
-- 
-- /Since: 2.30/
tlsConnectionSetDatabase ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.TlsDatabase.IsTlsDatabase b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> Maybe (b)
    -- ^ /@database@/: a t'GI.Gio.Objects.TlsDatabase.TlsDatabase'
    -> m ()
tlsConnectionSetDatabase :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTlsConnection a, IsTlsDatabase b) =>
a -> Maybe b -> m ()
tlsConnectionSetDatabase a
conn Maybe 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
maybeDatabase <- case Maybe b
database of
        Maybe b
Nothing -> Ptr TlsDatabase -> IO (Ptr TlsDatabase)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsDatabase
forall a. Ptr a
nullPtr
        Just b
jDatabase -> do
            Ptr TlsDatabase
jDatabase' <- b -> IO (Ptr TlsDatabase)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jDatabase
            Ptr TlsDatabase -> IO (Ptr TlsDatabase)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsDatabase
jDatabase'
    Ptr TlsConnection -> Ptr TlsDatabase -> IO ()
g_tls_connection_set_database Ptr TlsConnection
conn' Ptr TlsDatabase
maybeDatabase
    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
database b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TlsConnectionSetDatabaseMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsTlsConnection a, Gio.TlsDatabase.IsTlsDatabase b) => O.OverloadedMethod TlsConnectionSetDatabaseMethodInfo a signature where
    overloadedMethod = tlsConnectionSetDatabase

instance O.OverloadedMethodInfo TlsConnectionSetDatabaseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionSetDatabase",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionSetDatabase"
        })


#endif

-- method TlsConnection::set_interaction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a connection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interaction"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsInteraction" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an interaction object, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_set_interaction" g_tls_connection_set_interaction :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    Ptr Gio.TlsInteraction.TlsInteraction -> -- interaction : TInterface (Name {namespace = "Gio", name = "TlsInteraction"})
    IO ()

-- | Set the object that will be used to interact with the user. It will be used
-- for things like prompting the user for passwords.
-- 
-- The /@interaction@/ argument will normally be a derived subclass of
-- t'GI.Gio.Objects.TlsInteraction.TlsInteraction'. 'P.Nothing' can also be provided if no user interaction
-- should occur for this connection.
-- 
-- /Since: 2.30/
tlsConnectionSetInteraction ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a, Gio.TlsInteraction.IsTlsInteraction b) =>
    a
    -- ^ /@conn@/: a connection
    -> Maybe (b)
    -- ^ /@interaction@/: an interaction object, or 'P.Nothing'
    -> m ()
tlsConnectionSetInteraction :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTlsConnection a, IsTlsInteraction b) =>
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.OverloadedMethod TlsConnectionSetInteractionMethodInfo a signature where
    overloadedMethod = tlsConnectionSetInteraction

instance O.OverloadedMethodInfo TlsConnectionSetInteractionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionSetInteraction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionSetInteraction"
        })


#endif

-- method TlsConnection::set_rehandshake_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsRehandshakeMode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rehandshaking mode"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_set_rehandshake_mode" g_tls_connection_set_rehandshake_mode :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    CUInt ->                                -- mode : TInterface (Name {namespace = "Gio", name = "TlsRehandshakeMode"})
    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."] #-}
-- | Since GLib 2.64, changing the rehandshake mode is no longer supported
-- and will have no effect. With TLS 1.3, rehandshaking has been removed from
-- the TLS protocol, replaced by separate post-handshake authentication and
-- rekey operations.
-- 
-- /Since: 2.28/
tlsConnectionSetRehandshakeMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> Gio.Enums.TlsRehandshakeMode
    -- ^ /@mode@/: the rehandshaking mode
    -> m ()
tlsConnectionSetRehandshakeMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionSetRehandshakeModeMethodInfo a signature where
    overloadedMethod = tlsConnectionSetRehandshakeMode

instance O.OverloadedMethodInfo TlsConnectionSetRehandshakeModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionSetRehandshakeMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionSetRehandshakeMode"
        })


#endif

-- method TlsConnection::set_require_close_notify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "require_close_notify"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether or not to require close notification"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_set_require_close_notify" g_tls_connection_set_require_close_notify :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    CInt ->                                 -- require_close_notify : TBasicType TBoolean
    IO ()

-- | Sets whether or not /@conn@/ expects a proper TLS close notification
-- before the connection is closed. If this is 'P.True' (the default),
-- then /@conn@/ will expect to receive a TLS close notification from its
-- peer before the connection is closed, and will return a
-- 'GI.Gio.Enums.TlsErrorEof' error if the connection is closed without proper
-- notification (since this may indicate a network error, or
-- man-in-the-middle attack).
-- 
-- In some protocols, the application will know whether or not the
-- connection was closed cleanly based on application-level data
-- (because the application-level data includes a length field, or is
-- somehow self-delimiting); in this case, the close notify is
-- redundant and sometimes omitted. (TLS 1.1 explicitly allows this;
-- in TLS 1.0 it is technically an error, but often done anyway.) You
-- can use 'GI.Gio.Objects.TlsConnection.tlsConnectionSetRequireCloseNotify' to tell /@conn@/
-- to allow an \"unannounced\" connection close, in which case the close
-- will show up as a 0-length read, as in a non-TLS
-- t'GI.Gio.Objects.SocketConnection.SocketConnection', and it is up to the application to check that
-- the data has been fully received.
-- 
-- Note that this only affects the behavior when the peer closes the
-- connection; when the application calls 'GI.Gio.Objects.IOStream.iOStreamClose' itself
-- on /@conn@/, this will send a close notification regardless of the
-- setting of this property. If you explicitly want to do an unclean
-- close, you can close /@conn@/\'s [TlsConnection:baseIoStream]("GI.Gio.Objects.TlsConnection#g:attr:baseIoStream") rather
-- than closing /@conn@/ itself, but note that this may only be done when no other
-- operations are pending on /@conn@/ or the base I\/O stream.
-- 
-- /Since: 2.28/
tlsConnectionSetRequireCloseNotify ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> Bool
    -- ^ /@requireCloseNotify@/: whether or not to require close notification
    -> m ()
tlsConnectionSetRequireCloseNotify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionSetRequireCloseNotifyMethodInfo a signature where
    overloadedMethod = tlsConnectionSetRequireCloseNotify

instance O.OverloadedMethodInfo TlsConnectionSetRequireCloseNotifyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionSetRequireCloseNotify",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionSetRequireCloseNotify"
        })


#endif

-- method TlsConnection::set_use_system_certdb
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_system_certdb"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether to use the system certificate database"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_connection_set_use_system_certdb" g_tls_connection_set_use_system_certdb :: 
    Ptr TlsConnection ->                    -- conn : TInterface (Name {namespace = "Gio", name = "TlsConnection"})
    CInt ->                                 -- use_system_certdb : TBasicType TBoolean
    IO ()

{-# DEPRECATED tlsConnectionSetUseSystemCertdb ["(Since version 2.30)","Use 'GI.Gio.Objects.TlsConnection.tlsConnectionSetDatabase' instead"] #-}
-- | Sets whether /@conn@/ uses the system certificate database to verify
-- peer certificates. This is 'P.True' by default. If set to 'P.False', then
-- peer certificate validation will always set the
-- 'GI.Gio.Flags.TlsCertificateFlagsUnknownCa' error (meaning
-- [TlsConnection::acceptCertificate]("GI.Gio.Objects.TlsConnection#g:signal:acceptCertificate") will always be emitted on
-- client-side connections, unless that bit is not set in
-- t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection':@/validation-flags/@).
tlsConnectionSetUseSystemCertdb ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Objects.TlsConnection.TlsConnection'
    -> Bool
    -- ^ /@useSystemCertdb@/: whether to use the system certificate database
    -> m ()
tlsConnectionSetUseSystemCertdb :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsConnection a) =>
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.OverloadedMethod TlsConnectionSetUseSystemCertdbMethodInfo a signature where
    overloadedMethod = tlsConnectionSetUseSystemCertdb

instance O.OverloadedMethodInfo TlsConnectionSetUseSystemCertdbMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsConnection.tlsConnectionSetUseSystemCertdb",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsConnection.html#v:tlsConnectionSetUseSystemCertdb"
        })


#endif