{-# 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.Interfaces.DtlsConnection.DtlsConnection' is the base DTLS connection class type, which wraps
-- a t'GI.Gio.Interfaces.DatagramBased.DatagramBased' and provides DTLS encryption on top of it. Its
-- subclasses, t'GI.Gio.Interfaces.DtlsClientConnection.DtlsClientConnection' and t'GI.Gio.Interfaces.DtlsServerConnection.DtlsServerConnection',
-- implement client-side and server-side DTLS, respectively.
-- 
-- For TLS support, see t'GI.Gio.Objects.TlsConnection.TlsConnection'.
-- 
-- As DTLS is datagram based, t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' implements t'GI.Gio.Interfaces.DatagramBased.DatagramBased',
-- presenting a datagram-socket-like API for the encrypted connection. This
-- operates over a base datagram connection, which is also a t'GI.Gio.Interfaces.DatagramBased.DatagramBased'
-- (t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection':@/base-socket/@).
-- 
-- To close a DTLS connection, use 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionClose'.
-- 
-- Neither t'GI.Gio.Interfaces.DtlsServerConnection.DtlsServerConnection' or t'GI.Gio.Interfaces.DtlsClientConnection.DtlsClientConnection' set the peer address
-- on their base t'GI.Gio.Interfaces.DatagramBased.DatagramBased' if it is a t'GI.Gio.Objects.Socket.Socket' — it is up to the caller to
-- do that if they wish. If they do not, and 'GI.Gio.Objects.Socket.socketClose' is called on the
-- base socket, the t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' will not raise a 'GI.Gio.Enums.IOErrorEnumNotConnected'
-- error on further I\/O.
-- 
-- /Since: 2.48/

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

module GI.Gio.Interfaces.DtlsConnection
    ( 

-- * Exported types
    DtlsConnection(..)                      ,
    IsDtlsConnection                        ,
    toDtlsConnection                        ,


 -- * 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"), [close]("GI.Gio.Interfaces.DtlsConnection#g:method:close"), [closeAsync]("GI.Gio.Interfaces.DtlsConnection#g:method:closeAsync"), [closeFinish]("GI.Gio.Interfaces.DtlsConnection#g:method:closeFinish"), [conditionCheck]("GI.Gio.Interfaces.DatagramBased#g:method:conditionCheck"), [conditionWait]("GI.Gio.Interfaces.DatagramBased#g:method:conditionWait"), [createSource]("GI.Gio.Interfaces.DatagramBased#g:method:createSource"), [emitAcceptCertificate]("GI.Gio.Interfaces.DtlsConnection#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.Interfaces.DtlsConnection#g:method:handshake"), [handshakeAsync]("GI.Gio.Interfaces.DtlsConnection#g:method:handshakeAsync"), [handshakeFinish]("GI.Gio.Interfaces.DtlsConnection#g:method:handshakeFinish"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [receiveMessages]("GI.Gio.Interfaces.DatagramBased#g:method:receiveMessages"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [sendMessages]("GI.Gio.Interfaces.DatagramBased#g:method:sendMessages"), [shutdown]("GI.Gio.Interfaces.DtlsConnection#g:method:shutdown"), [shutdownAsync]("GI.Gio.Interfaces.DtlsConnection#g:method:shutdownAsync"), [shutdownFinish]("GI.Gio.Interfaces.DtlsConnection#g:method:shutdownFinish"), [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.Interfaces.DtlsConnection#g:method:getCertificate"), [getChannelBindingData]("GI.Gio.Interfaces.DtlsConnection#g:method:getChannelBindingData"), [getCiphersuiteName]("GI.Gio.Interfaces.DtlsConnection#g:method:getCiphersuiteName"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDatabase]("GI.Gio.Interfaces.DtlsConnection#g:method:getDatabase"), [getInteraction]("GI.Gio.Interfaces.DtlsConnection#g:method:getInteraction"), [getNegotiatedProtocol]("GI.Gio.Interfaces.DtlsConnection#g:method:getNegotiatedProtocol"), [getPeerCertificate]("GI.Gio.Interfaces.DtlsConnection#g:method:getPeerCertificate"), [getPeerCertificateErrors]("GI.Gio.Interfaces.DtlsConnection#g:method:getPeerCertificateErrors"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getProtocolVersion]("GI.Gio.Interfaces.DtlsConnection#g:method:getProtocolVersion"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRehandshakeMode]("GI.Gio.Interfaces.DtlsConnection#g:method:getRehandshakeMode"), [getRequireCloseNotify]("GI.Gio.Interfaces.DtlsConnection#g:method:getRequireCloseNotify").
-- 
-- ==== Setters
-- [setAdvertisedProtocols]("GI.Gio.Interfaces.DtlsConnection#g:method:setAdvertisedProtocols"), [setCertificate]("GI.Gio.Interfaces.DtlsConnection#g:method:setCertificate"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDatabase]("GI.Gio.Interfaces.DtlsConnection#g:method:setDatabase"), [setInteraction]("GI.Gio.Interfaces.DtlsConnection#g:method:setInteraction"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRehandshakeMode]("GI.Gio.Interfaces.DtlsConnection#g:method:setRehandshakeMode"), [setRequireCloseNotify]("GI.Gio.Interfaces.DtlsConnection#g:method:setRequireCloseNotify").

#if defined(ENABLE_OVERLOADING)
    ResolveDtlsConnectionMethod             ,
#endif

-- ** close #method:close#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionCloseMethodInfo           ,
#endif
    dtlsConnectionClose                     ,


-- ** closeAsync #method:closeAsync#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionCloseAsyncMethodInfo      ,
#endif
    dtlsConnectionCloseAsync                ,


-- ** closeFinish #method:closeFinish#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionCloseFinishMethodInfo     ,
#endif
    dtlsConnectionCloseFinish               ,


-- ** emitAcceptCertificate #method:emitAcceptCertificate#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionEmitAcceptCertificateMethodInfo,
#endif
    dtlsConnectionEmitAcceptCertificate     ,


-- ** getCertificate #method:getCertificate#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetCertificateMethodInfo  ,
#endif
    dtlsConnectionGetCertificate            ,


-- ** getChannelBindingData #method:getChannelBindingData#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetChannelBindingDataMethodInfo,
#endif
    dtlsConnectionGetChannelBindingData     ,


-- ** getCiphersuiteName #method:getCiphersuiteName#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetCiphersuiteNameMethodInfo,
#endif
    dtlsConnectionGetCiphersuiteName        ,


-- ** getDatabase #method:getDatabase#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetDatabaseMethodInfo     ,
#endif
    dtlsConnectionGetDatabase               ,


-- ** getInteraction #method:getInteraction#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetInteractionMethodInfo  ,
#endif
    dtlsConnectionGetInteraction            ,


-- ** getNegotiatedProtocol #method:getNegotiatedProtocol#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetNegotiatedProtocolMethodInfo,
#endif
    dtlsConnectionGetNegotiatedProtocol     ,


-- ** getPeerCertificate #method:getPeerCertificate#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetPeerCertificateMethodInfo,
#endif
    dtlsConnectionGetPeerCertificate        ,


-- ** getPeerCertificateErrors #method:getPeerCertificateErrors#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetPeerCertificateErrorsMethodInfo,
#endif
    dtlsConnectionGetPeerCertificateErrors  ,


-- ** getProtocolVersion #method:getProtocolVersion#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetProtocolVersionMethodInfo,
#endif
    dtlsConnectionGetProtocolVersion        ,


-- ** getRehandshakeMode #method:getRehandshakeMode#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetRehandshakeModeMethodInfo,
#endif
    dtlsConnectionGetRehandshakeMode        ,


-- ** getRequireCloseNotify #method:getRequireCloseNotify#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionGetRequireCloseNotifyMethodInfo,
#endif
    dtlsConnectionGetRequireCloseNotify     ,


-- ** handshake #method:handshake#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionHandshakeMethodInfo       ,
#endif
    dtlsConnectionHandshake                 ,


-- ** handshakeAsync #method:handshakeAsync#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionHandshakeAsyncMethodInfo  ,
#endif
    dtlsConnectionHandshakeAsync            ,


-- ** handshakeFinish #method:handshakeFinish#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionHandshakeFinishMethodInfo ,
#endif
    dtlsConnectionHandshakeFinish           ,


-- ** setAdvertisedProtocols #method:setAdvertisedProtocols#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionSetAdvertisedProtocolsMethodInfo,
#endif
    dtlsConnectionSetAdvertisedProtocols    ,


-- ** setCertificate #method:setCertificate#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionSetCertificateMethodInfo  ,
#endif
    dtlsConnectionSetCertificate            ,


-- ** setDatabase #method:setDatabase#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionSetDatabaseMethodInfo     ,
#endif
    dtlsConnectionSetDatabase               ,


-- ** setInteraction #method:setInteraction#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionSetInteractionMethodInfo  ,
#endif
    dtlsConnectionSetInteraction            ,


-- ** setRehandshakeMode #method:setRehandshakeMode#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionSetRehandshakeModeMethodInfo,
#endif
    dtlsConnectionSetRehandshakeMode        ,


-- ** setRequireCloseNotify #method:setRequireCloseNotify#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionSetRequireCloseNotifyMethodInfo,
#endif
    dtlsConnectionSetRequireCloseNotify     ,


-- ** shutdown #method:shutdown#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionShutdownMethodInfo        ,
#endif
    dtlsConnectionShutdown                  ,


-- ** shutdownAsync #method:shutdownAsync#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionShutdownAsyncMethodInfo   ,
#endif
    dtlsConnectionShutdownAsync             ,


-- ** shutdownFinish #method:shutdownFinish#

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionShutdownFinishMethodInfo  ,
#endif
    dtlsConnectionShutdownFinish            ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionAdvertisedProtocolsPropertyInfo,
#endif
    clearDtlsConnectionAdvertisedProtocols  ,
    constructDtlsConnectionAdvertisedProtocols,
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionAdvertisedProtocols       ,
#endif
    getDtlsConnectionAdvertisedProtocols    ,
    setDtlsConnectionAdvertisedProtocols    ,


-- ** baseSocket #attr:baseSocket#
-- | The t'GI.Gio.Interfaces.DatagramBased.DatagramBased' that the connection wraps. Note that this may be any
-- implementation of t'GI.Gio.Interfaces.DatagramBased.DatagramBased', not just a t'GI.Gio.Objects.Socket.Socket'.
-- 
-- /Since: 2.48/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionBaseSocketPropertyInfo    ,
#endif
    constructDtlsConnectionBaseSocket       ,
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionBaseSocket                ,
#endif
    getDtlsConnectionBaseSocket             ,


-- ** certificate #attr:certificate#
-- | The connection\'s certificate; see
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetCertificate'.
-- 
-- /Since: 2.48/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionCertificatePropertyInfo   ,
#endif
    constructDtlsConnectionCertificate      ,
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionCertificate               ,
#endif
    getDtlsConnectionCertificate            ,
    setDtlsConnectionCertificate            ,


-- ** ciphersuiteName #attr:ciphersuiteName#
-- | The name of the DTLS ciphersuite in use. See 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetCiphersuiteName'.
-- 
-- /Since: 2.70/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionCiphersuiteNamePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionCiphersuiteName           ,
#endif
    getDtlsConnectionCiphersuiteName        ,


-- ** 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'.
-- 
-- When using a non-default database, t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' must fall back to using
-- the t'GI.Gio.Objects.TlsDatabase.TlsDatabase' to perform certificate verification using
-- 'GI.Gio.Objects.TlsDatabase.tlsDatabaseVerifyChain', which means certificate verification will
-- not be able to make use of TLS session context. This may be less secure.
-- For example, if you create your own t'GI.Gio.Objects.TlsDatabase.TlsDatabase' that just wraps the
-- default t'GI.Gio.Objects.TlsDatabase.TlsDatabase', you might expect that you have not changed anything,
-- but this is not true because you may have altered the behavior of
-- t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' by causing it to use 'GI.Gio.Objects.TlsDatabase.tlsDatabaseVerifyChain'. See the
-- documentation of 'GI.Gio.Objects.TlsDatabase.tlsDatabaseVerifyChain' for more details on specific
-- security checks that may not be performed. Accordingly, setting a
-- non-default database is discouraged except for specialty applications with
-- unusual security requirements.
-- 
-- /Since: 2.48/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionDatabasePropertyInfo      ,
#endif
    clearDtlsConnectionDatabase             ,
    constructDtlsConnectionDatabase         ,
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionDatabase                  ,
#endif
    getDtlsConnectionDatabase               ,
    setDtlsConnectionDatabase               ,


-- ** 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.48/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionInteractionPropertyInfo   ,
#endif
    clearDtlsConnectionInteraction          ,
    constructDtlsConnectionInteraction      ,
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionInteraction               ,
#endif
    getDtlsConnectionInteraction            ,
    setDtlsConnectionInteraction            ,


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

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionNegotiatedProtocolPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionNegotiatedProtocol        ,
#endif
    getDtlsConnectionNegotiatedProtocol     ,


-- ** 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 [DtlsConnection::acceptCertificate]("GI.Gio.Interfaces.DtlsConnection#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.48/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionPeerCertificatePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionPeerCertificate           ,
#endif
    getDtlsConnectionPeerCertificate        ,


-- ** peerCertificateErrors #attr:peerCertificateErrors#
-- | The errors noticed while verifying
-- t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection':@/peer-certificate/@. Normally this should be 0, but
-- it may not be if t'GI.Gio.Interfaces.DtlsClientConnection.DtlsClientConnection':@/validation-flags/@ is not
-- 'GI.Gio.Flags.TlsCertificateFlagsValidateAll', or if
-- [DtlsConnection::acceptCertificate]("GI.Gio.Interfaces.DtlsConnection#g:signal:acceptCertificate") overrode the default
-- behavior.
-- 
-- GLib guarantees that if certificate verification fails, at least
-- one error will be set, but it does not guarantee that all possible
-- errors will be set. Accordingly, you may not safely decide to
-- ignore any particular type of error. For example, it would be
-- incorrect to mask 'GI.Gio.Flags.TlsCertificateFlagsExpired' if you want to allow
-- expired certificates, because this could potentially be the only
-- error flag set even if other problems exist with the certificate.
-- 
-- /Since: 2.48/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionPeerCertificateErrorsPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionPeerCertificateErrors     ,
#endif
    getDtlsConnectionPeerCertificateErrors  ,


-- ** protocolVersion #attr:protocolVersion#
-- | The DTLS protocol version in use. See 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetProtocolVersion'.
-- 
-- /Since: 2.70/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionProtocolVersionPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionProtocolVersion           ,
#endif
    getDtlsConnectionProtocolVersion        ,


-- ** rehandshakeMode #attr:rehandshakeMode#
-- | The rehandshaking mode. See
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetRehandshakeMode'.
-- 
-- /Since: 2.48/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionRehandshakeModePropertyInfo,
#endif
    constructDtlsConnectionRehandshakeMode  ,
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionRehandshakeMode           ,
#endif
    getDtlsConnectionRehandshakeMode        ,
    setDtlsConnectionRehandshakeMode        ,


-- ** requireCloseNotify #attr:requireCloseNotify#
-- | Whether or not proper TLS close notification is required.
-- See 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetRequireCloseNotify'.
-- 
-- /Since: 2.48/

#if defined(ENABLE_OVERLOADING)
    DtlsConnectionRequireCloseNotifyPropertyInfo,
#endif
    constructDtlsConnectionRequireCloseNotify,
#if defined(ENABLE_OVERLOADING)
    dtlsConnectionRequireCloseNotify        ,
#endif
    getDtlsConnectionRequireCloseNotify     ,
    setDtlsConnectionRequireCloseNotify     ,




 -- * Signals


-- ** acceptCertificate #signal:acceptCertificate#

    DtlsConnectionAcceptCertificateCallback ,
#if defined(ENABLE_OVERLOADING)
    DtlsConnectionAcceptCertificateSignalInfo,
#endif
    afterDtlsConnectionAcceptCertificate    ,
    onDtlsConnectionAcceptCertificate       ,




    ) 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.GHashTable as B.GHT
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.Interfaces.DatagramBased as Gio.DatagramBased
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
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

-- interface DtlsConnection 
-- | Memory-managed wrapper type.
newtype DtlsConnection = DtlsConnection (SP.ManagedPtr DtlsConnection)
    deriving (DtlsConnection -> DtlsConnection -> Bool
(DtlsConnection -> DtlsConnection -> Bool)
-> (DtlsConnection -> DtlsConnection -> Bool) -> Eq DtlsConnection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DtlsConnection -> DtlsConnection -> Bool
== :: DtlsConnection -> DtlsConnection -> Bool
$c/= :: DtlsConnection -> DtlsConnection -> Bool
/= :: DtlsConnection -> DtlsConnection -> Bool
Eq)

instance SP.ManagedPtrNewtype DtlsConnection where
    toManagedPtr :: DtlsConnection -> ManagedPtr DtlsConnection
toManagedPtr (DtlsConnection ManagedPtr DtlsConnection
p) = ManagedPtr DtlsConnection
p

foreign import ccall "g_dtls_connection_get_type"
    c_g_dtls_connection_get_type :: IO B.Types.GType

instance B.Types.TypedObject DtlsConnection where
    glibType :: IO GType
glibType = IO GType
c_g_dtls_connection_get_type

instance B.Types.GObject DtlsConnection

-- | Type class for types which can be safely cast to `DtlsConnection`, for instance with `toDtlsConnection`.
class (SP.GObject o, O.IsDescendantOf DtlsConnection o) => IsDtlsConnection o
instance (SP.GObject o, O.IsDescendantOf DtlsConnection o) => IsDtlsConnection o

instance O.HasParentTypes DtlsConnection
type instance O.ParentTypes DtlsConnection = '[Gio.DatagramBased.DatagramBased, GObject.Object.Object]

-- | Cast to `DtlsConnection`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDtlsConnection :: (MIO.MonadIO m, IsDtlsConnection o) => o -> m DtlsConnection
toDtlsConnection :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m DtlsConnection
toDtlsConnection = IO DtlsConnection -> m DtlsConnection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DtlsConnection -> m DtlsConnection)
-> (o -> IO DtlsConnection) -> o -> m DtlsConnection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DtlsConnection -> DtlsConnection)
-> o -> IO DtlsConnection
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DtlsConnection -> DtlsConnection
DtlsConnection

-- | Convert 'DtlsConnection' 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 DtlsConnection) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_dtls_connection_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DtlsConnection -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DtlsConnection
P.Nothing = Ptr GValue -> Ptr DtlsConnection -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DtlsConnection
forall a. Ptr a
FP.nullPtr :: FP.Ptr DtlsConnection)
    gvalueSet_ Ptr GValue
gv (P.Just DtlsConnection
obj) = DtlsConnection -> (Ptr DtlsConnection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DtlsConnection
obj (Ptr GValue -> Ptr DtlsConnection -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DtlsConnection)
gvalueGet_ Ptr GValue
gv = do
        Ptr DtlsConnection
ptr <- Ptr GValue -> IO (Ptr DtlsConnection)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DtlsConnection)
        if Ptr DtlsConnection
ptr Ptr DtlsConnection -> Ptr DtlsConnection -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DtlsConnection
forall a. Ptr a
FP.nullPtr
        then DtlsConnection -> Maybe DtlsConnection
forall a. a -> Maybe a
P.Just (DtlsConnection -> Maybe DtlsConnection)
-> IO DtlsConnection -> IO (Maybe DtlsConnection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DtlsConnection -> DtlsConnection)
-> Ptr DtlsConnection -> IO DtlsConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DtlsConnection -> DtlsConnection
DtlsConnection Ptr DtlsConnection
ptr
        else Maybe DtlsConnection -> IO (Maybe DtlsConnection)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DtlsConnection
forall a. Maybe a
P.Nothing
        
    

-- 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' dtlsConnection #advertisedProtocols
-- @
getDtlsConnectionAdvertisedProtocols :: (MonadIO m, IsDtlsConnection o) => o -> m (Maybe [T.Text])
getDtlsConnectionAdvertisedProtocols :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe [Text])
getDtlsConnectionAdvertisedProtocols o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall a. IO a -> m a
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' dtlsConnection [ #advertisedProtocols 'Data.GI.Base.Attributes.:=' value ]
-- @
setDtlsConnectionAdvertisedProtocols :: (MonadIO m, IsDtlsConnection o) => o -> [T.Text] -> m ()
setDtlsConnectionAdvertisedProtocols :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> [Text] -> m ()
setDtlsConnectionAdvertisedProtocols o
obj [Text]
val = IO () -> m ()
forall a. IO a -> m a
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`.
constructDtlsConnectionAdvertisedProtocols :: (IsDtlsConnection o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructDtlsConnectionAdvertisedProtocols :: forall o (m :: * -> *).
(IsDtlsConnection o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructDtlsConnectionAdvertisedProtocols [Text]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
-- @
clearDtlsConnectionAdvertisedProtocols :: (MonadIO m, IsDtlsConnection o) => o -> m ()
clearDtlsConnectionAdvertisedProtocols :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m ()
clearDtlsConnectionAdvertisedProtocols o
obj = IO () -> m ()
forall a. IO a -> m a
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 DtlsConnectionAdvertisedProtocolsPropertyInfo
instance AttrInfo DtlsConnectionAdvertisedProtocolsPropertyInfo where
    type AttrAllowedOps DtlsConnectionAdvertisedProtocolsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DtlsConnectionAdvertisedProtocolsPropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionAdvertisedProtocolsPropertyInfo = (~) [T.Text]
    type AttrTransferTypeConstraint DtlsConnectionAdvertisedProtocolsPropertyInfo = (~) [T.Text]
    type AttrTransferType DtlsConnectionAdvertisedProtocolsPropertyInfo = [T.Text]
    type AttrGetType DtlsConnectionAdvertisedProtocolsPropertyInfo = (Maybe [T.Text])
    type AttrLabel DtlsConnectionAdvertisedProtocolsPropertyInfo = "advertised-protocols"
    type AttrOrigin DtlsConnectionAdvertisedProtocolsPropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionAdvertisedProtocols
    attrSet = setDtlsConnectionAdvertisedProtocols
    attrTransfer _ v = do
        return v
    attrConstruct = constructDtlsConnectionAdvertisedProtocols
    attrClear = clearDtlsConnectionAdvertisedProtocols
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.advertisedProtocols"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:advertisedProtocols"
        })
#endif

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

-- | Get the value of the “@base-socket@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dtlsConnection #baseSocket
-- @
getDtlsConnectionBaseSocket :: (MonadIO m, IsDtlsConnection o) => o -> m (Maybe Gio.DatagramBased.DatagramBased)
getDtlsConnectionBaseSocket :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe DatagramBased)
getDtlsConnectionBaseSocket o
obj = IO (Maybe DatagramBased) -> m (Maybe DatagramBased)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DatagramBased) -> m (Maybe DatagramBased))
-> IO (Maybe DatagramBased) -> m (Maybe DatagramBased)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DatagramBased -> DatagramBased)
-> IO (Maybe DatagramBased)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"base-socket" ManagedPtr DatagramBased -> DatagramBased
Gio.DatagramBased.DatagramBased

-- | Construct a `GValueConstruct` with valid value for the “@base-socket@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDtlsConnectionBaseSocket :: (IsDtlsConnection o, MIO.MonadIO m, Gio.DatagramBased.IsDatagramBased a) => a -> m (GValueConstruct o)
constructDtlsConnectionBaseSocket :: forall o (m :: * -> *) a.
(IsDtlsConnection o, MonadIO m, IsDatagramBased a) =>
a -> m (GValueConstruct o)
constructDtlsConnectionBaseSocket a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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-socket" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionBaseSocketPropertyInfo
instance AttrInfo DtlsConnectionBaseSocketPropertyInfo where
    type AttrAllowedOps DtlsConnectionBaseSocketPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DtlsConnectionBaseSocketPropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionBaseSocketPropertyInfo = Gio.DatagramBased.IsDatagramBased
    type AttrTransferTypeConstraint DtlsConnectionBaseSocketPropertyInfo = Gio.DatagramBased.IsDatagramBased
    type AttrTransferType DtlsConnectionBaseSocketPropertyInfo = Gio.DatagramBased.DatagramBased
    type AttrGetType DtlsConnectionBaseSocketPropertyInfo = (Maybe Gio.DatagramBased.DatagramBased)
    type AttrLabel DtlsConnectionBaseSocketPropertyInfo = "base-socket"
    type AttrOrigin DtlsConnectionBaseSocketPropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionBaseSocket
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.DatagramBased.DatagramBased v
    attrConstruct = constructDtlsConnectionBaseSocket
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.baseSocket"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:baseSocket"
        })
#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' dtlsConnection #certificate
-- @
getDtlsConnectionCertificate :: (MonadIO m, IsDtlsConnection o) => o -> m (Maybe Gio.TlsCertificate.TlsCertificate)
getDtlsConnectionCertificate :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe TlsCertificate)
getDtlsConnectionCertificate o
obj = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall a. IO a -> m a
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' dtlsConnection [ #certificate 'Data.GI.Base.Attributes.:=' value ]
-- @
setDtlsConnectionCertificate :: (MonadIO m, IsDtlsConnection o, Gio.TlsCertificate.IsTlsCertificate a) => o -> a -> m ()
setDtlsConnectionCertificate :: forall (m :: * -> *) o a.
(MonadIO m, IsDtlsConnection o, IsTlsCertificate a) =>
o -> a -> m ()
setDtlsConnectionCertificate o
obj a
val = IO () -> m ()
forall a. IO a -> m a
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`.
constructDtlsConnectionCertificate :: (IsDtlsConnection o, MIO.MonadIO m, Gio.TlsCertificate.IsTlsCertificate a) => a -> m (GValueConstruct o)
constructDtlsConnectionCertificate :: forall o (m :: * -> *) a.
(IsDtlsConnection o, MonadIO m, IsTlsCertificate a) =>
a -> m (GValueConstruct o)
constructDtlsConnectionCertificate a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 DtlsConnectionCertificatePropertyInfo
instance AttrInfo DtlsConnectionCertificatePropertyInfo where
    type AttrAllowedOps DtlsConnectionCertificatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DtlsConnectionCertificatePropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionCertificatePropertyInfo = Gio.TlsCertificate.IsTlsCertificate
    type AttrTransferTypeConstraint DtlsConnectionCertificatePropertyInfo = Gio.TlsCertificate.IsTlsCertificate
    type AttrTransferType DtlsConnectionCertificatePropertyInfo = Gio.TlsCertificate.TlsCertificate
    type AttrGetType DtlsConnectionCertificatePropertyInfo = (Maybe Gio.TlsCertificate.TlsCertificate)
    type AttrLabel DtlsConnectionCertificatePropertyInfo = "certificate"
    type AttrOrigin DtlsConnectionCertificatePropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionCertificate
    attrSet = setDtlsConnectionCertificate
    attrTransfer _ v = do
        unsafeCastTo Gio.TlsCertificate.TlsCertificate v
    attrConstruct = constructDtlsConnectionCertificate
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.certificate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #ciphersuiteName
-- @
getDtlsConnectionCiphersuiteName :: (MonadIO m, IsDtlsConnection o) => o -> m (Maybe T.Text)
getDtlsConnectionCiphersuiteName :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe Text)
getDtlsConnectionCiphersuiteName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 DtlsConnectionCiphersuiteNamePropertyInfo
instance AttrInfo DtlsConnectionCiphersuiteNamePropertyInfo where
    type AttrAllowedOps DtlsConnectionCiphersuiteNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DtlsConnectionCiphersuiteNamePropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionCiphersuiteNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DtlsConnectionCiphersuiteNamePropertyInfo = (~) ()
    type AttrTransferType DtlsConnectionCiphersuiteNamePropertyInfo = ()
    type AttrGetType DtlsConnectionCiphersuiteNamePropertyInfo = (Maybe T.Text)
    type AttrLabel DtlsConnectionCiphersuiteNamePropertyInfo = "ciphersuite-name"
    type AttrOrigin DtlsConnectionCiphersuiteNamePropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionCiphersuiteName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.ciphersuiteName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #database
-- @
getDtlsConnectionDatabase :: (MonadIO m, IsDtlsConnection o) => o -> m (Maybe Gio.TlsDatabase.TlsDatabase)
getDtlsConnectionDatabase :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe TlsDatabase)
getDtlsConnectionDatabase o
obj = IO (Maybe TlsDatabase) -> m (Maybe TlsDatabase)
forall a. IO a -> m a
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' dtlsConnection [ #database 'Data.GI.Base.Attributes.:=' value ]
-- @
setDtlsConnectionDatabase :: (MonadIO m, IsDtlsConnection o, Gio.TlsDatabase.IsTlsDatabase a) => o -> a -> m ()
setDtlsConnectionDatabase :: forall (m :: * -> *) o a.
(MonadIO m, IsDtlsConnection o, IsTlsDatabase a) =>
o -> a -> m ()
setDtlsConnectionDatabase o
obj a
val = IO () -> m ()
forall a. IO a -> m a
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`.
constructDtlsConnectionDatabase :: (IsDtlsConnection o, MIO.MonadIO m, Gio.TlsDatabase.IsTlsDatabase a) => a -> m (GValueConstruct o)
constructDtlsConnectionDatabase :: forall o (m :: * -> *) a.
(IsDtlsConnection o, MonadIO m, IsTlsDatabase a) =>
a -> m (GValueConstruct o)
constructDtlsConnectionDatabase a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
-- @
clearDtlsConnectionDatabase :: (MonadIO m, IsDtlsConnection o) => o -> m ()
clearDtlsConnectionDatabase :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m ()
clearDtlsConnectionDatabase o
obj = IO () -> m ()
forall a. IO a -> m a
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 DtlsConnectionDatabasePropertyInfo
instance AttrInfo DtlsConnectionDatabasePropertyInfo where
    type AttrAllowedOps DtlsConnectionDatabasePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DtlsConnectionDatabasePropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionDatabasePropertyInfo = Gio.TlsDatabase.IsTlsDatabase
    type AttrTransferTypeConstraint DtlsConnectionDatabasePropertyInfo = Gio.TlsDatabase.IsTlsDatabase
    type AttrTransferType DtlsConnectionDatabasePropertyInfo = Gio.TlsDatabase.TlsDatabase
    type AttrGetType DtlsConnectionDatabasePropertyInfo = (Maybe Gio.TlsDatabase.TlsDatabase)
    type AttrLabel DtlsConnectionDatabasePropertyInfo = "database"
    type AttrOrigin DtlsConnectionDatabasePropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionDatabase
    attrSet = setDtlsConnectionDatabase
    attrTransfer _ v = do
        unsafeCastTo Gio.TlsDatabase.TlsDatabase v
    attrConstruct = constructDtlsConnectionDatabase
    attrClear = clearDtlsConnectionDatabase
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.database"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #interaction
-- @
getDtlsConnectionInteraction :: (MonadIO m, IsDtlsConnection o) => o -> m (Maybe Gio.TlsInteraction.TlsInteraction)
getDtlsConnectionInteraction :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe TlsInteraction)
getDtlsConnectionInteraction o
obj = IO (Maybe TlsInteraction) -> m (Maybe TlsInteraction)
forall a. IO a -> m a
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' dtlsConnection [ #interaction 'Data.GI.Base.Attributes.:=' value ]
-- @
setDtlsConnectionInteraction :: (MonadIO m, IsDtlsConnection o, Gio.TlsInteraction.IsTlsInteraction a) => o -> a -> m ()
setDtlsConnectionInteraction :: forall (m :: * -> *) o a.
(MonadIO m, IsDtlsConnection o, IsTlsInteraction a) =>
o -> a -> m ()
setDtlsConnectionInteraction o
obj a
val = IO () -> m ()
forall a. IO a -> m a
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`.
constructDtlsConnectionInteraction :: (IsDtlsConnection o, MIO.MonadIO m, Gio.TlsInteraction.IsTlsInteraction a) => a -> m (GValueConstruct o)
constructDtlsConnectionInteraction :: forall o (m :: * -> *) a.
(IsDtlsConnection o, MonadIO m, IsTlsInteraction a) =>
a -> m (GValueConstruct o)
constructDtlsConnectionInteraction a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
-- @
clearDtlsConnectionInteraction :: (MonadIO m, IsDtlsConnection o) => o -> m ()
clearDtlsConnectionInteraction :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m ()
clearDtlsConnectionInteraction o
obj = IO () -> m ()
forall a. IO a -> m a
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 DtlsConnectionInteractionPropertyInfo
instance AttrInfo DtlsConnectionInteractionPropertyInfo where
    type AttrAllowedOps DtlsConnectionInteractionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DtlsConnectionInteractionPropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionInteractionPropertyInfo = Gio.TlsInteraction.IsTlsInteraction
    type AttrTransferTypeConstraint DtlsConnectionInteractionPropertyInfo = Gio.TlsInteraction.IsTlsInteraction
    type AttrTransferType DtlsConnectionInteractionPropertyInfo = Gio.TlsInteraction.TlsInteraction
    type AttrGetType DtlsConnectionInteractionPropertyInfo = (Maybe Gio.TlsInteraction.TlsInteraction)
    type AttrLabel DtlsConnectionInteractionPropertyInfo = "interaction"
    type AttrOrigin DtlsConnectionInteractionPropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionInteraction
    attrSet = setDtlsConnectionInteraction
    attrTransfer _ v = do
        unsafeCastTo Gio.TlsInteraction.TlsInteraction v
    attrConstruct = constructDtlsConnectionInteraction
    attrClear = clearDtlsConnectionInteraction
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.interaction"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #negotiatedProtocol
-- @
getDtlsConnectionNegotiatedProtocol :: (MonadIO m, IsDtlsConnection o) => o -> m (Maybe T.Text)
getDtlsConnectionNegotiatedProtocol :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe Text)
getDtlsConnectionNegotiatedProtocol o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 DtlsConnectionNegotiatedProtocolPropertyInfo
instance AttrInfo DtlsConnectionNegotiatedProtocolPropertyInfo where
    type AttrAllowedOps DtlsConnectionNegotiatedProtocolPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DtlsConnectionNegotiatedProtocolPropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionNegotiatedProtocolPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DtlsConnectionNegotiatedProtocolPropertyInfo = (~) ()
    type AttrTransferType DtlsConnectionNegotiatedProtocolPropertyInfo = ()
    type AttrGetType DtlsConnectionNegotiatedProtocolPropertyInfo = (Maybe T.Text)
    type AttrLabel DtlsConnectionNegotiatedProtocolPropertyInfo = "negotiated-protocol"
    type AttrOrigin DtlsConnectionNegotiatedProtocolPropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionNegotiatedProtocol
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.negotiatedProtocol"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #peerCertificate
-- @
getDtlsConnectionPeerCertificate :: (MonadIO m, IsDtlsConnection o) => o -> m (Maybe Gio.TlsCertificate.TlsCertificate)
getDtlsConnectionPeerCertificate :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe TlsCertificate)
getDtlsConnectionPeerCertificate o
obj = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall a. IO a -> m a
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 DtlsConnectionPeerCertificatePropertyInfo
instance AttrInfo DtlsConnectionPeerCertificatePropertyInfo where
    type AttrAllowedOps DtlsConnectionPeerCertificatePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DtlsConnectionPeerCertificatePropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionPeerCertificatePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DtlsConnectionPeerCertificatePropertyInfo = (~) ()
    type AttrTransferType DtlsConnectionPeerCertificatePropertyInfo = ()
    type AttrGetType DtlsConnectionPeerCertificatePropertyInfo = (Maybe Gio.TlsCertificate.TlsCertificate)
    type AttrLabel DtlsConnectionPeerCertificatePropertyInfo = "peer-certificate"
    type AttrOrigin DtlsConnectionPeerCertificatePropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionPeerCertificate
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.peerCertificate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #peerCertificateErrors
-- @
getDtlsConnectionPeerCertificateErrors :: (MonadIO m, IsDtlsConnection o) => o -> m [Gio.Flags.TlsCertificateFlags]
getDtlsConnectionPeerCertificateErrors :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m [TlsCertificateFlags]
getDtlsConnectionPeerCertificateErrors o
obj = IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall a. IO a -> m a
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 DtlsConnectionPeerCertificateErrorsPropertyInfo
instance AttrInfo DtlsConnectionPeerCertificateErrorsPropertyInfo where
    type AttrAllowedOps DtlsConnectionPeerCertificateErrorsPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DtlsConnectionPeerCertificateErrorsPropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionPeerCertificateErrorsPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DtlsConnectionPeerCertificateErrorsPropertyInfo = (~) ()
    type AttrTransferType DtlsConnectionPeerCertificateErrorsPropertyInfo = ()
    type AttrGetType DtlsConnectionPeerCertificateErrorsPropertyInfo = [Gio.Flags.TlsCertificateFlags]
    type AttrLabel DtlsConnectionPeerCertificateErrorsPropertyInfo = "peer-certificate-errors"
    type AttrOrigin DtlsConnectionPeerCertificateErrorsPropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionPeerCertificateErrors
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.peerCertificateErrors"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #protocolVersion
-- @
getDtlsConnectionProtocolVersion :: (MonadIO m, IsDtlsConnection o) => o -> m Gio.Enums.TlsProtocolVersion
getDtlsConnectionProtocolVersion :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m TlsProtocolVersion
getDtlsConnectionProtocolVersion o
obj = IO TlsProtocolVersion -> m TlsProtocolVersion
forall a. IO a -> m a
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 DtlsConnectionProtocolVersionPropertyInfo
instance AttrInfo DtlsConnectionProtocolVersionPropertyInfo where
    type AttrAllowedOps DtlsConnectionProtocolVersionPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DtlsConnectionProtocolVersionPropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionProtocolVersionPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DtlsConnectionProtocolVersionPropertyInfo = (~) ()
    type AttrTransferType DtlsConnectionProtocolVersionPropertyInfo = ()
    type AttrGetType DtlsConnectionProtocolVersionPropertyInfo = Gio.Enums.TlsProtocolVersion
    type AttrLabel DtlsConnectionProtocolVersionPropertyInfo = "protocol-version"
    type AttrOrigin DtlsConnectionProtocolVersionPropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionProtocolVersion
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.protocolVersion"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #rehandshakeMode
-- @
getDtlsConnectionRehandshakeMode :: (MonadIO m, IsDtlsConnection o) => o -> m Gio.Enums.TlsRehandshakeMode
getDtlsConnectionRehandshakeMode :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m TlsRehandshakeMode
getDtlsConnectionRehandshakeMode o
obj = IO TlsRehandshakeMode -> m TlsRehandshakeMode
forall a. IO a -> m a
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' dtlsConnection [ #rehandshakeMode 'Data.GI.Base.Attributes.:=' value ]
-- @
setDtlsConnectionRehandshakeMode :: (MonadIO m, IsDtlsConnection o) => o -> Gio.Enums.TlsRehandshakeMode -> m ()
setDtlsConnectionRehandshakeMode :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> TlsRehandshakeMode -> m ()
setDtlsConnectionRehandshakeMode o
obj TlsRehandshakeMode
val = IO () -> m ()
forall a. IO a -> m a
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`.
constructDtlsConnectionRehandshakeMode :: (IsDtlsConnection o, MIO.MonadIO m) => Gio.Enums.TlsRehandshakeMode -> m (GValueConstruct o)
constructDtlsConnectionRehandshakeMode :: forall o (m :: * -> *).
(IsDtlsConnection o, MonadIO m) =>
TlsRehandshakeMode -> m (GValueConstruct o)
constructDtlsConnectionRehandshakeMode TlsRehandshakeMode
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 DtlsConnectionRehandshakeModePropertyInfo
instance AttrInfo DtlsConnectionRehandshakeModePropertyInfo where
    type AttrAllowedOps DtlsConnectionRehandshakeModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DtlsConnectionRehandshakeModePropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionRehandshakeModePropertyInfo = (~) Gio.Enums.TlsRehandshakeMode
    type AttrTransferTypeConstraint DtlsConnectionRehandshakeModePropertyInfo = (~) Gio.Enums.TlsRehandshakeMode
    type AttrTransferType DtlsConnectionRehandshakeModePropertyInfo = Gio.Enums.TlsRehandshakeMode
    type AttrGetType DtlsConnectionRehandshakeModePropertyInfo = Gio.Enums.TlsRehandshakeMode
    type AttrLabel DtlsConnectionRehandshakeModePropertyInfo = "rehandshake-mode"
    type AttrOrigin DtlsConnectionRehandshakeModePropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionRehandshakeMode
    attrSet = setDtlsConnectionRehandshakeMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructDtlsConnectionRehandshakeMode
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.rehandshakeMode"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.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' dtlsConnection #requireCloseNotify
-- @
getDtlsConnectionRequireCloseNotify :: (MonadIO m, IsDtlsConnection o) => o -> m Bool
getDtlsConnectionRequireCloseNotify :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m Bool
getDtlsConnectionRequireCloseNotify o
obj = IO Bool -> m Bool
forall a. IO a -> m a
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' dtlsConnection [ #requireCloseNotify 'Data.GI.Base.Attributes.:=' value ]
-- @
setDtlsConnectionRequireCloseNotify :: (MonadIO m, IsDtlsConnection o) => o -> Bool -> m ()
setDtlsConnectionRequireCloseNotify :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> Bool -> m ()
setDtlsConnectionRequireCloseNotify o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
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`.
constructDtlsConnectionRequireCloseNotify :: (IsDtlsConnection o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDtlsConnectionRequireCloseNotify :: forall o (m :: * -> *).
(IsDtlsConnection o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDtlsConnectionRequireCloseNotify Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 DtlsConnectionRequireCloseNotifyPropertyInfo
instance AttrInfo DtlsConnectionRequireCloseNotifyPropertyInfo where
    type AttrAllowedOps DtlsConnectionRequireCloseNotifyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DtlsConnectionRequireCloseNotifyPropertyInfo = IsDtlsConnection
    type AttrSetTypeConstraint DtlsConnectionRequireCloseNotifyPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint DtlsConnectionRequireCloseNotifyPropertyInfo = (~) Bool
    type AttrTransferType DtlsConnectionRequireCloseNotifyPropertyInfo = Bool
    type AttrGetType DtlsConnectionRequireCloseNotifyPropertyInfo = Bool
    type AttrLabel DtlsConnectionRequireCloseNotifyPropertyInfo = "require-close-notify"
    type AttrOrigin DtlsConnectionRequireCloseNotifyPropertyInfo = DtlsConnection
    attrGet = getDtlsConnectionRequireCloseNotify
    attrSet = setDtlsConnectionRequireCloseNotify
    attrTransfer _ v = do
        return v
    attrConstruct = constructDtlsConnectionRequireCloseNotify
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.requireCloseNotify"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:requireCloseNotify"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DtlsConnection
type instance O.AttributeList DtlsConnection = DtlsConnectionAttributeList
type DtlsConnectionAttributeList = ('[ '("advertisedProtocols", DtlsConnectionAdvertisedProtocolsPropertyInfo), '("baseSocket", DtlsConnectionBaseSocketPropertyInfo), '("certificate", DtlsConnectionCertificatePropertyInfo), '("ciphersuiteName", DtlsConnectionCiphersuiteNamePropertyInfo), '("database", DtlsConnectionDatabasePropertyInfo), '("interaction", DtlsConnectionInteractionPropertyInfo), '("negotiatedProtocol", DtlsConnectionNegotiatedProtocolPropertyInfo), '("peerCertificate", DtlsConnectionPeerCertificatePropertyInfo), '("peerCertificateErrors", DtlsConnectionPeerCertificateErrorsPropertyInfo), '("protocolVersion", DtlsConnectionProtocolVersionPropertyInfo), '("rehandshakeMode", DtlsConnectionRehandshakeModePropertyInfo), '("requireCloseNotify", DtlsConnectionRequireCloseNotifyPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dtlsConnectionAdvertisedProtocols :: AttrLabelProxy "advertisedProtocols"
dtlsConnectionAdvertisedProtocols = AttrLabelProxy

dtlsConnectionBaseSocket :: AttrLabelProxy "baseSocket"
dtlsConnectionBaseSocket = AttrLabelProxy

dtlsConnectionCertificate :: AttrLabelProxy "certificate"
dtlsConnectionCertificate = AttrLabelProxy

dtlsConnectionCiphersuiteName :: AttrLabelProxy "ciphersuiteName"
dtlsConnectionCiphersuiteName = AttrLabelProxy

dtlsConnectionDatabase :: AttrLabelProxy "database"
dtlsConnectionDatabase = AttrLabelProxy

dtlsConnectionInteraction :: AttrLabelProxy "interaction"
dtlsConnectionInteraction = AttrLabelProxy

dtlsConnectionNegotiatedProtocol :: AttrLabelProxy "negotiatedProtocol"
dtlsConnectionNegotiatedProtocol = AttrLabelProxy

dtlsConnectionPeerCertificate :: AttrLabelProxy "peerCertificate"
dtlsConnectionPeerCertificate = AttrLabelProxy

dtlsConnectionPeerCertificateErrors :: AttrLabelProxy "peerCertificateErrors"
dtlsConnectionPeerCertificateErrors = AttrLabelProxy

dtlsConnectionProtocolVersion :: AttrLabelProxy "protocolVersion"
dtlsConnectionProtocolVersion = AttrLabelProxy

dtlsConnectionRehandshakeMode :: AttrLabelProxy "rehandshakeMode"
dtlsConnectionRehandshakeMode = AttrLabelProxy

dtlsConnectionRequireCloseNotify :: AttrLabelProxy "requireCloseNotify"
dtlsConnectionRequireCloseNotify = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDtlsConnectionMethod (t :: Symbol) (o :: *) :: * where
    ResolveDtlsConnectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDtlsConnectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDtlsConnectionMethod "close" o = DtlsConnectionCloseMethodInfo
    ResolveDtlsConnectionMethod "closeAsync" o = DtlsConnectionCloseAsyncMethodInfo
    ResolveDtlsConnectionMethod "closeFinish" o = DtlsConnectionCloseFinishMethodInfo
    ResolveDtlsConnectionMethod "conditionCheck" o = Gio.DatagramBased.DatagramBasedConditionCheckMethodInfo
    ResolveDtlsConnectionMethod "conditionWait" o = Gio.DatagramBased.DatagramBasedConditionWaitMethodInfo
    ResolveDtlsConnectionMethod "createSource" o = Gio.DatagramBased.DatagramBasedCreateSourceMethodInfo
    ResolveDtlsConnectionMethod "emitAcceptCertificate" o = DtlsConnectionEmitAcceptCertificateMethodInfo
    ResolveDtlsConnectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDtlsConnectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDtlsConnectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDtlsConnectionMethod "handshake" o = DtlsConnectionHandshakeMethodInfo
    ResolveDtlsConnectionMethod "handshakeAsync" o = DtlsConnectionHandshakeAsyncMethodInfo
    ResolveDtlsConnectionMethod "handshakeFinish" o = DtlsConnectionHandshakeFinishMethodInfo
    ResolveDtlsConnectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDtlsConnectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDtlsConnectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDtlsConnectionMethod "receiveMessages" o = Gio.DatagramBased.DatagramBasedReceiveMessagesMethodInfo
    ResolveDtlsConnectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDtlsConnectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDtlsConnectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDtlsConnectionMethod "sendMessages" o = Gio.DatagramBased.DatagramBasedSendMessagesMethodInfo
    ResolveDtlsConnectionMethod "shutdown" o = DtlsConnectionShutdownMethodInfo
    ResolveDtlsConnectionMethod "shutdownAsync" o = DtlsConnectionShutdownAsyncMethodInfo
    ResolveDtlsConnectionMethod "shutdownFinish" o = DtlsConnectionShutdownFinishMethodInfo
    ResolveDtlsConnectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDtlsConnectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDtlsConnectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDtlsConnectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDtlsConnectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDtlsConnectionMethod "getCertificate" o = DtlsConnectionGetCertificateMethodInfo
    ResolveDtlsConnectionMethod "getChannelBindingData" o = DtlsConnectionGetChannelBindingDataMethodInfo
    ResolveDtlsConnectionMethod "getCiphersuiteName" o = DtlsConnectionGetCiphersuiteNameMethodInfo
    ResolveDtlsConnectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDtlsConnectionMethod "getDatabase" o = DtlsConnectionGetDatabaseMethodInfo
    ResolveDtlsConnectionMethod "getInteraction" o = DtlsConnectionGetInteractionMethodInfo
    ResolveDtlsConnectionMethod "getNegotiatedProtocol" o = DtlsConnectionGetNegotiatedProtocolMethodInfo
    ResolveDtlsConnectionMethod "getPeerCertificate" o = DtlsConnectionGetPeerCertificateMethodInfo
    ResolveDtlsConnectionMethod "getPeerCertificateErrors" o = DtlsConnectionGetPeerCertificateErrorsMethodInfo
    ResolveDtlsConnectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDtlsConnectionMethod "getProtocolVersion" o = DtlsConnectionGetProtocolVersionMethodInfo
    ResolveDtlsConnectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDtlsConnectionMethod "getRehandshakeMode" o = DtlsConnectionGetRehandshakeModeMethodInfo
    ResolveDtlsConnectionMethod "getRequireCloseNotify" o = DtlsConnectionGetRequireCloseNotifyMethodInfo
    ResolveDtlsConnectionMethod "setAdvertisedProtocols" o = DtlsConnectionSetAdvertisedProtocolsMethodInfo
    ResolveDtlsConnectionMethod "setCertificate" o = DtlsConnectionSetCertificateMethodInfo
    ResolveDtlsConnectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDtlsConnectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDtlsConnectionMethod "setDatabase" o = DtlsConnectionSetDatabaseMethodInfo
    ResolveDtlsConnectionMethod "setInteraction" o = DtlsConnectionSetInteractionMethodInfo
    ResolveDtlsConnectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDtlsConnectionMethod "setRehandshakeMode" o = DtlsConnectionSetRehandshakeModeMethodInfo
    ResolveDtlsConnectionMethod "setRequireCloseNotify" o = DtlsConnectionSetRequireCloseNotifyMethodInfo
    ResolveDtlsConnectionMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDtlsConnectionMethod t DtlsConnection, O.OverloadedMethod info DtlsConnection p) => OL.IsLabel t (DtlsConnection -> 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 ~ ResolveDtlsConnectionMethod t DtlsConnection, O.OverloadedMethod info DtlsConnection p, R.HasField t DtlsConnection p) => R.HasField t DtlsConnection p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- method DtlsConnection::close
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_close" g_dtls_connection_close :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Close the DTLS connection. This is equivalent to calling
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdown' to shut down both sides of the connection.
-- 
-- Closing a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' waits for all buffered but untransmitted data to
-- be sent before it completes. It then sends a @close_notify@ DTLS alert to the
-- peer and may wait for a @close_notify@ to be received from the peer. It does
-- not close the underlying t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection':@/base-socket/@; that must be closed
-- separately.
-- 
-- Once /@conn@/ is closed, all other operations will return 'GI.Gio.Enums.IOErrorEnumClosed'.
-- Closing a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' multiple times will not return an error.
-- 
-- @/GDtlsConnections/@ will be automatically closed when the last reference is
-- dropped, but you might want to call this function to make sure resources are
-- released as early as possible.
-- 
-- If /@cancellable@/ is cancelled, the t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' may be left
-- partially-closed and any pending untransmitted data may be lost. Call
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionClose' again to complete closing the t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'.
-- 
-- /Since: 2.48/
dtlsConnectionClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dtlsConnectionClose :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Maybe b -> m ()
dtlsConnectionClose a
conn Maybe b
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 a. a -> IO a
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 a. a -> IO a
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 DtlsConnection
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_dtls_connection_close Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionCloseMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod DtlsConnectionCloseMethodInfo a signature where
    overloadedMethod = dtlsConnectionClose

instance O.OverloadedMethodInfo DtlsConnectionCloseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionClose",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionClose"
        })


#endif

-- method DtlsConnection::close_async
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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 close operation 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_dtls_connection_close_async" g_dtls_connection_close_async :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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 close the DTLS connection. See 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionClose' for
-- more information.
-- 
-- /Since: 2.48/
dtlsConnectionCloseAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> 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 close operation is complete
    -> m ()
dtlsConnectionCloseAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
dtlsConnectionCloseAsync a
conn Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 DtlsConnection
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_dtls_connection_close_async Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionCloseAsyncMethodInfo
instance (signature ~ (Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod DtlsConnectionCloseAsyncMethodInfo a signature where
    overloadedMethod = dtlsConnectionCloseAsync

instance O.OverloadedMethodInfo DtlsConnectionCloseAsyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionCloseAsync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionCloseAsync"
        })


#endif

-- method DtlsConnection::close_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_close_finish" g_dtls_connection_close_finish :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finish an asynchronous TLS close operation. See 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionClose'
-- for more information.
-- 
-- /Since: 2.48/
dtlsConnectionCloseFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dtlsConnectionCloseFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsAsyncResult b) =>
a -> b -> m ()
dtlsConnectionCloseFinish a
conn b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 DtlsConnection
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_dtls_connection_close_finish Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionCloseFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod DtlsConnectionCloseFinishMethodInfo a signature where
    overloadedMethod = dtlsConnectionCloseFinish

instance O.OverloadedMethodInfo DtlsConnectionCloseFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionCloseFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionCloseFinish"
        })


#endif

-- method DtlsConnection::emit_accept_certificate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_emit_accept_certificate" g_dtls_connection_emit_accept_certificate :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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.Interfaces.DtlsConnection.DtlsConnection' implementations to emit the
-- [DtlsConnection::acceptCertificate]("GI.Gio.Interfaces.DtlsConnection#g:signal:acceptCertificate") signal.
-- 
-- /Since: 2.48/
dtlsConnectionEmitAcceptCertificate ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> 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@/
dtlsConnectionEmitAcceptCertificate :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a,
 IsTlsCertificate b) =>
a -> b -> [TlsCertificateFlags] -> m Bool
dtlsConnectionEmitAcceptCertificate a
conn b
peerCert [TlsCertificateFlags]
errors = IO Bool -> m Bool
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 DtlsConnection -> Ptr TlsCertificate -> CUInt -> IO CInt
g_dtls_connection_emit_accept_certificate Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionEmitAcceptCertificateMethodInfo
instance (signature ~ (b -> [Gio.Flags.TlsCertificateFlags] -> m Bool), MonadIO m, IsDtlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) => O.OverloadedMethod DtlsConnectionEmitAcceptCertificateMethodInfo a signature where
    overloadedMethod = dtlsConnectionEmitAcceptCertificate

instance O.OverloadedMethodInfo DtlsConnectionEmitAcceptCertificateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionEmitAcceptCertificate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionEmitAcceptCertificate"
        })


#endif

-- method DtlsConnection::get_certificate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_get_certificate" g_dtls_connection_get_certificate :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    IO (Ptr Gio.TlsCertificate.TlsCertificate)

-- | Gets /@conn@/\'s certificate, as set by
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetCertificate'.
-- 
-- /Since: 2.48/
dtlsConnectionGetCertificate ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> m (Maybe Gio.TlsCertificate.TlsCertificate)
    -- ^ __Returns:__ /@conn@/\'s certificate, or 'P.Nothing'
dtlsConnectionGetCertificate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe TlsCertificate)
dtlsConnectionGetCertificate a
conn = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    Ptr TlsCertificate
result <- Ptr DtlsConnection -> IO (Ptr TlsCertificate)
g_dtls_connection_get_certificate Ptr DtlsConnection
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsCertificate
maybeResult

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

instance O.OverloadedMethodInfo DtlsConnectionGetCertificateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetCertificate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetCertificate"
        })


#endif

-- method DtlsConnection::get_channel_binding_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_get_channel_binding_data" g_dtls_connection_get_channel_binding_data :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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/
dtlsConnectionGetChannelBindingData ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Gio.Enums.TlsChannelBindingType
    -- ^ /@type@/: t'GI.Gio.Enums.TlsChannelBindingType' type of data to fetch
    -> m (ByteString)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dtlsConnectionGetChannelBindingData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> TlsChannelBindingType -> m ByteString
dtlsConnectionGetChannelBindingData a
conn TlsChannelBindingType
type_ = IO ByteString -> m ByteString
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 DtlsConnection
-> CUInt -> Ptr (Ptr GByteArray) -> Ptr (Ptr GError) -> IO CInt
g_dtls_connection_get_channel_binding_data Ptr DtlsConnection
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 a. a -> IO a
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 DtlsConnectionGetChannelBindingDataMethodInfo
instance (signature ~ (Gio.Enums.TlsChannelBindingType -> m (ByteString)), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetChannelBindingDataMethodInfo a signature where
    overloadedMethod = dtlsConnectionGetChannelBindingData

instance O.OverloadedMethodInfo DtlsConnectionGetChannelBindingDataMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetChannelBindingData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetChannelBindingData"
        })


#endif

-- method DtlsConnection::get_ciphersuite_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDTlsConnection" , 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_dtls_connection_get_ciphersuite_name" g_dtls_connection_get_ciphersuite_name :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    IO CString

-- | Returns the name of the current DTLS 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/
dtlsConnectionGetCiphersuiteName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a @/GDTlsConnection/@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The name of the current DTLS ciphersuite, or 'P.Nothing'
dtlsConnectionGetCiphersuiteName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe Text)
dtlsConnectionGetCiphersuiteName a
conn = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    CString
result <- Ptr DtlsConnection -> IO CString
g_dtls_connection_get_ciphersuite_name Ptr DtlsConnection
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetCiphersuiteNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetCiphersuiteNameMethodInfo a signature where
    overloadedMethod = dtlsConnectionGetCiphersuiteName

instance O.OverloadedMethodInfo DtlsConnectionGetCiphersuiteNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetCiphersuiteName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetCiphersuiteName"
        })


#endif

-- method DtlsConnection::get_database
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_get_database" g_dtls_connection_get_database :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    IO (Ptr Gio.TlsDatabase.TlsDatabase)

-- | Gets the certificate database that /@conn@/ uses to verify
-- peer certificates. See 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetDatabase'.
-- 
-- /Since: 2.48/
dtlsConnectionGetDatabase ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> m (Maybe Gio.TlsDatabase.TlsDatabase)
    -- ^ __Returns:__ the certificate database that /@conn@/ uses or 'P.Nothing'
dtlsConnectionGetDatabase :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe TlsDatabase)
dtlsConnectionGetDatabase a
conn = IO (Maybe TlsDatabase) -> m (Maybe TlsDatabase)
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    Ptr TlsDatabase
result <- Ptr DtlsConnection -> IO (Ptr TlsDatabase)
g_dtls_connection_get_database Ptr DtlsConnection
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsDatabase
maybeResult

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

instance O.OverloadedMethodInfo DtlsConnectionGetDatabaseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetDatabase",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetDatabase"
        })


#endif

-- method DtlsConnection::get_interaction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , 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_dtls_connection_get_interaction" g_dtls_connection_get_interaction :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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.48/
dtlsConnectionGetInteraction ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a connection
    -> m (Maybe Gio.TlsInteraction.TlsInteraction)
    -- ^ __Returns:__ The interaction object.
dtlsConnectionGetInteraction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe TlsInteraction)
dtlsConnectionGetInteraction a
conn = IO (Maybe TlsInteraction) -> m (Maybe TlsInteraction)
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    Ptr TlsInteraction
result <- Ptr DtlsConnection -> IO (Ptr TlsInteraction)
g_dtls_connection_get_interaction Ptr DtlsConnection
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsInteraction
maybeResult

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

instance O.OverloadedMethodInfo DtlsConnectionGetInteractionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetInteraction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetInteraction"
        })


#endif

-- method DtlsConnection::get_negotiated_protocol
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_get_negotiated_protocol" g_dtls_connection_get_negotiated_protocol :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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.Interfaces.DtlsConnection.dtlsConnectionSetAdvertisedProtocols'.
-- 
-- /Since: 2.60/
dtlsConnectionGetNegotiatedProtocol ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the negotiated protocol, or 'P.Nothing'
dtlsConnectionGetNegotiatedProtocol :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe Text)
dtlsConnectionGetNegotiatedProtocol a
conn = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    CString
result <- Ptr DtlsConnection -> IO CString
g_dtls_connection_get_negotiated_protocol Ptr DtlsConnection
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetNegotiatedProtocolMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetNegotiatedProtocolMethodInfo a signature where
    overloadedMethod = dtlsConnectionGetNegotiatedProtocol

instance O.OverloadedMethodInfo DtlsConnectionGetNegotiatedProtocolMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetNegotiatedProtocol",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetNegotiatedProtocol"
        })


#endif

-- method DtlsConnection::get_peer_certificate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_get_peer_certificate" g_dtls_connection_get_peer_certificate :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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
-- [DtlsConnection::acceptCertificate]("GI.Gio.Interfaces.DtlsConnection#g:signal:acceptCertificate").)
-- 
-- /Since: 2.48/
dtlsConnectionGetPeerCertificate ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> m (Maybe Gio.TlsCertificate.TlsCertificate)
    -- ^ __Returns:__ /@conn@/\'s peer\'s certificate, or 'P.Nothing'
dtlsConnectionGetPeerCertificate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe TlsCertificate)
dtlsConnectionGetPeerCertificate a
conn = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    Ptr TlsCertificate
result <- Ptr DtlsConnection -> IO (Ptr TlsCertificate)
g_dtls_connection_get_peer_certificate Ptr DtlsConnection
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsCertificate
maybeResult

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

instance O.OverloadedMethodInfo DtlsConnectionGetPeerCertificateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetPeerCertificate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetPeerCertificate"
        })


#endif

-- method DtlsConnection::get_peer_certificate_errors
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_get_peer_certificate_errors" g_dtls_connection_get_peer_certificate_errors :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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 [DtlsConnection::acceptCertificate]("GI.Gio.Interfaces.DtlsConnection#g:signal:acceptCertificate").)
-- 
-- /Since: 2.48/
dtlsConnectionGetPeerCertificateErrors ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> m [Gio.Flags.TlsCertificateFlags]
    -- ^ __Returns:__ /@conn@/\'s peer\'s certificate errors
dtlsConnectionGetPeerCertificateErrors :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m [TlsCertificateFlags]
dtlsConnectionGetPeerCertificateErrors a
conn = IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    CUInt
result <- Ptr DtlsConnection -> IO CUInt
g_dtls_connection_get_peer_certificate_errors Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [TlsCertificateFlags]
result'

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetPeerCertificateErrorsMethodInfo
instance (signature ~ (m [Gio.Flags.TlsCertificateFlags]), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetPeerCertificateErrorsMethodInfo a signature where
    overloadedMethod = dtlsConnectionGetPeerCertificateErrors

instance O.OverloadedMethodInfo DtlsConnectionGetPeerCertificateErrorsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetPeerCertificateErrors",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetPeerCertificateErrors"
        })


#endif

-- method DtlsConnection::get_protocol_version
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDTlsConnection" , 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_dtls_connection_get_protocol_version" g_dtls_connection_get_protocol_version :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    IO CUInt

-- | Returns the current DTLS 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/
dtlsConnectionGetProtocolVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a @/GDTlsConnection/@
    -> m Gio.Enums.TlsProtocolVersion
    -- ^ __Returns:__ The current DTLS protocol version
dtlsConnectionGetProtocolVersion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m TlsProtocolVersion
dtlsConnectionGetProtocolVersion a
conn = IO TlsProtocolVersion -> m TlsProtocolVersion
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    CUInt
result <- Ptr DtlsConnection -> IO CUInt
g_dtls_connection_get_protocol_version Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TlsProtocolVersion
result'

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

instance O.OverloadedMethodInfo DtlsConnectionGetProtocolVersionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetProtocolVersion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetProtocolVersion"
        })


#endif

-- method DtlsConnection::get_rehandshake_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_get_rehandshake_mode" g_dtls_connection_get_rehandshake_mode :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    IO CUInt

{-# DEPRECATED dtlsConnectionGetRehandshakeMode ["(Since version 2.64.)","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.Interfaces.DtlsConnection.dtlsConnectionSetRehandshakeMode' for details.
-- 
-- /Since: 2.48/
dtlsConnectionGetRehandshakeMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> m Gio.Enums.TlsRehandshakeMode
    -- ^ __Returns:__ 'GI.Gio.Enums.TlsRehandshakeModeSafely'
dtlsConnectionGetRehandshakeMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m TlsRehandshakeMode
dtlsConnectionGetRehandshakeMode a
conn = IO TlsRehandshakeMode -> m TlsRehandshakeMode
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    CUInt
result <- Ptr DtlsConnection -> IO CUInt
g_dtls_connection_get_rehandshake_mode Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TlsRehandshakeMode
result'

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetRehandshakeModeMethodInfo
instance (signature ~ (m Gio.Enums.TlsRehandshakeMode), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetRehandshakeModeMethodInfo a signature where
    overloadedMethod = dtlsConnectionGetRehandshakeMode

instance O.OverloadedMethodInfo DtlsConnectionGetRehandshakeModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetRehandshakeMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetRehandshakeMode"
        })


#endif

-- method DtlsConnection::get_require_close_notify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_get_require_close_notify" g_dtls_connection_get_require_close_notify :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    IO CInt

-- | Tests whether or not /@conn@/ expects a proper TLS close notification
-- when the connection is closed. See
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetRequireCloseNotify' for details.
-- 
-- /Since: 2.48/
dtlsConnectionGetRequireCloseNotify ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@conn@/ requires a proper TLS close notification.
dtlsConnectionGetRequireCloseNotify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m Bool
dtlsConnectionGetRequireCloseNotify a
conn = IO Bool -> m Bool
forall a. IO a -> m a
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 DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    CInt
result <- Ptr DtlsConnection -> IO CInt
g_dtls_connection_get_require_close_notify Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetRequireCloseNotifyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetRequireCloseNotifyMethodInfo a signature where
    overloadedMethod = dtlsConnectionGetRequireCloseNotify

instance O.OverloadedMethodInfo DtlsConnectionGetRequireCloseNotifyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetRequireCloseNotify",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetRequireCloseNotify"
        })


#endif

-- method DtlsConnection::handshake
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_handshake" g_dtls_connection_handshake :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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, t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' will handle this for you automatically
-- when you try to send or receive data on the connection. You can call
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionHandshake' 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.Interfaces.DtlsConnection.dtlsConnectionHandshake' 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.
-- 
-- t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'::@/accept_certificate/@ may be emitted during the
-- handshake.
-- 
-- /Since: 2.48/
dtlsConnectionHandshake ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dtlsConnectionHandshake :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Maybe b -> m ()
dtlsConnectionHandshake a
conn Maybe b
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 a. a -> IO a
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 a. a -> IO a
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 DtlsConnection
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_dtls_connection_handshake Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionHandshakeMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod DtlsConnectionHandshakeMethodInfo a signature where
    overloadedMethod = dtlsConnectionHandshake

instance O.OverloadedMethodInfo DtlsConnectionHandshakeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionHandshake",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionHandshake"
        })


#endif

-- method DtlsConnection::handshake_async
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_handshake_async" g_dtls_connection_handshake_async :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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.Interfaces.DtlsConnection.dtlsConnectionHandshake' for more information.
-- 
-- /Since: 2.48/
dtlsConnectionHandshakeAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> 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 ()
dtlsConnectionHandshakeAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
dtlsConnectionHandshakeAsync a
conn Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 DtlsConnection
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_dtls_connection_handshake_async Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionHandshakeAsyncMethodInfo
instance (signature ~ (Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod DtlsConnectionHandshakeAsyncMethodInfo a signature where
    overloadedMethod = dtlsConnectionHandshakeAsync

instance O.OverloadedMethodInfo DtlsConnectionHandshakeAsyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionHandshakeAsync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionHandshakeAsync"
        })


#endif

-- method DtlsConnection::handshake_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_handshake_finish" g_dtls_connection_handshake_finish :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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.Interfaces.DtlsConnection.dtlsConnectionHandshake' for more information.
-- 
-- /Since: 2.48/
dtlsConnectionHandshakeFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dtlsConnectionHandshakeFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsAsyncResult b) =>
a -> b -> m ()
dtlsConnectionHandshakeFinish a
conn b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 DtlsConnection
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_dtls_connection_handshake_finish Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionHandshakeFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod DtlsConnectionHandshakeFinishMethodInfo a signature where
    overloadedMethod = dtlsConnectionHandshakeFinish

instance O.OverloadedMethodInfo DtlsConnectionHandshakeFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionHandshakeFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionHandshakeFinish"
        })


#endif

-- method DtlsConnection::set_advertised_protocols
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_set_advertised_protocols" g_dtls_connection_set_advertised_protocols :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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.Interfaces.DtlsConnection.dtlsConnectionGetNegotiatedProtocol' 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/
dtlsConnectionSetAdvertisedProtocols ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Maybe ([T.Text])
    -- ^ /@protocols@/: a 'P.Nothing'-terminated
    --   array of ALPN protocol names (eg, \"http\/1.1\", \"h2\"), or 'P.Nothing'
    -> m ()
dtlsConnectionSetAdvertisedProtocols :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> Maybe [Text] -> m ()
dtlsConnectionSetAdvertisedProtocols a
conn Maybe [Text]
protocols = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jProtocols'
    Ptr DtlsConnection -> Ptr CString -> IO ()
g_dtls_connection_set_advertised_protocols Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionSetAdvertisedProtocolsMethodInfo
instance (signature ~ (Maybe ([T.Text]) -> m ()), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionSetAdvertisedProtocolsMethodInfo a signature where
    overloadedMethod = dtlsConnectionSetAdvertisedProtocols

instance O.OverloadedMethodInfo DtlsConnectionSetAdvertisedProtocolsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetAdvertisedProtocols",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetAdvertisedProtocols"
        })


#endif

-- method DtlsConnection::set_certificate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_set_certificate" g_dtls_connection_set_certificate :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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.DtlsServerConnection.DtlsServerConnection', it is
-- mandatory to set this, and that will normally be done at construct
-- time.
-- 
-- For a t'GI.Gio.Interfaces.DtlsClientConnection.DtlsClientConnection', 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.DtlsClientConnection.dtlsClientConnectionGetAcceptedCas' 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.DtlsClientConnection.dtlsClientConnectionGetAcceptedCas' will return
-- non-'P.Nothing'.)
-- 
-- /Since: 2.48/
dtlsConnectionSetCertificate ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> b
    -- ^ /@certificate@/: the certificate to use for /@conn@/
    -> m ()
dtlsConnectionSetCertificate :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a,
 IsTlsCertificate b) =>
a -> b -> m ()
dtlsConnectionSetCertificate a
conn b
certificate = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 DtlsConnection -> Ptr TlsCertificate -> IO ()
g_dtls_connection_set_certificate Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionSetCertificateMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDtlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) => O.OverloadedMethod DtlsConnectionSetCertificateMethodInfo a signature where
    overloadedMethod = dtlsConnectionSetCertificate

instance O.OverloadedMethodInfo DtlsConnectionSetCertificateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetCertificate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetCertificate"
        })


#endif

-- method DtlsConnection::set_database
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_set_database" g_dtls_connection_set_database :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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
-- [DtlsConnection::acceptCertificate]("GI.Gio.Interfaces.DtlsConnection#g:signal:acceptCertificate") will always be emitted on
-- client-side connections, unless that bit is not set in
-- t'GI.Gio.Interfaces.DtlsClientConnection.DtlsClientConnection':@/validation-flags/@).
-- 
-- There are nonintuitive security implications when using a non-default
-- database. See t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection':@/database/@ for details.
-- 
-- /Since: 2.48/
dtlsConnectionSetDatabase ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.TlsDatabase.IsTlsDatabase b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Maybe (b)
    -- ^ /@database@/: a t'GI.Gio.Objects.TlsDatabase.TlsDatabase'
    -> m ()
dtlsConnectionSetDatabase :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsTlsDatabase b) =>
a -> Maybe b -> m ()
dtlsConnectionSetDatabase a
conn Maybe b
database = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsDatabase
jDatabase'
    Ptr DtlsConnection -> Ptr TlsDatabase -> IO ()
g_dtls_connection_set_database Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo DtlsConnectionSetDatabaseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetDatabase",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetDatabase"
        })


#endif

-- method DtlsConnection::set_interaction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , 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_dtls_connection_set_interaction" g_dtls_connection_set_interaction :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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.48/
dtlsConnectionSetInteraction ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.TlsInteraction.IsTlsInteraction b) =>
    a
    -- ^ /@conn@/: a connection
    -> Maybe (b)
    -- ^ /@interaction@/: an interaction object, or 'P.Nothing'
    -> m ()
dtlsConnectionSetInteraction :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a,
 IsTlsInteraction b) =>
a -> Maybe b -> m ()
dtlsConnectionSetInteraction a
conn Maybe b
interaction = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsInteraction
jInteraction'
    Ptr DtlsConnection -> Ptr TlsInteraction -> IO ()
g_dtls_connection_set_interaction Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionSetInteractionMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDtlsConnection a, Gio.TlsInteraction.IsTlsInteraction b) => O.OverloadedMethod DtlsConnectionSetInteractionMethodInfo a signature where
    overloadedMethod = dtlsConnectionSetInteraction

instance O.OverloadedMethodInfo DtlsConnectionSetInteractionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetInteraction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetInteraction"
        })


#endif

-- method DtlsConnection::set_rehandshake_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_set_rehandshake_mode" g_dtls_connection_set_rehandshake_mode :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    CUInt ->                                -- mode : TInterface (Name {namespace = "Gio", name = "TlsRehandshakeMode"})
    IO ()

{-# DEPRECATED dtlsConnectionSetRehandshakeMode ["(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.48/
dtlsConnectionSetRehandshakeMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Gio.Enums.TlsRehandshakeMode
    -- ^ /@mode@/: the rehandshaking mode
    -> m ()
dtlsConnectionSetRehandshakeMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> TlsRehandshakeMode -> m ()
dtlsConnectionSetRehandshakeMode a
conn TlsRehandshakeMode
mode = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 DtlsConnection -> CUInt -> IO ()
g_dtls_connection_set_rehandshake_mode Ptr DtlsConnection
conn' CUInt
mode'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionSetRehandshakeModeMethodInfo
instance (signature ~ (Gio.Enums.TlsRehandshakeMode -> m ()), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionSetRehandshakeModeMethodInfo a signature where
    overloadedMethod = dtlsConnectionSetRehandshakeMode

instance O.OverloadedMethodInfo DtlsConnectionSetRehandshakeModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetRehandshakeMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetRehandshakeMode"
        })


#endif

-- method DtlsConnection::set_require_close_notify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_set_require_close_notify" g_dtls_connection_set_require_close_notify :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    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 may be omitted. You
-- can use 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetRequireCloseNotify' 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.Interfaces.DatagramBased.DatagramBased', 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.Interfaces.DtlsConnection.dtlsConnectionCloseAsync' on
-- /@conn@/ itself, 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 t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection':@/base-socket/@ rather
-- than closing /@conn@/ itself.
-- 
-- /Since: 2.48/
dtlsConnectionSetRequireCloseNotify ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Bool
    -- ^ /@requireCloseNotify@/: whether or not to require close notification
    -> m ()
dtlsConnectionSetRequireCloseNotify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> Bool -> m ()
dtlsConnectionSetRequireCloseNotify a
conn Bool
requireCloseNotify = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 DtlsConnection -> CInt -> IO ()
g_dtls_connection_set_require_close_notify Ptr DtlsConnection
conn' CInt
requireCloseNotify'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionSetRequireCloseNotifyMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionSetRequireCloseNotifyMethodInfo a signature where
    overloadedMethod = dtlsConnectionSetRequireCloseNotify

instance O.OverloadedMethodInfo DtlsConnectionSetRequireCloseNotifyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetRequireCloseNotify",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetRequireCloseNotify"
        })


#endif

-- method DtlsConnection::shutdown
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shutdown_read"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to stop reception of incoming datagrams"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shutdown_write"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to stop sending outgoing datagrams"
--                 , 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_dtls_connection_shutdown" g_dtls_connection_shutdown :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    CInt ->                                 -- shutdown_read : TBasicType TBoolean
    CInt ->                                 -- shutdown_write : TBasicType TBoolean
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Shut down part or all of a DTLS connection.
-- 
-- If /@shutdownRead@/ is 'P.True' then the receiving side of the connection is shut
-- down, and further reading is disallowed. Subsequent calls to
-- 'GI.Gio.Interfaces.DatagramBased.datagramBasedReceiveMessages' will return 'GI.Gio.Enums.IOErrorEnumClosed'.
-- 
-- If /@shutdownWrite@/ is 'P.True' then the sending side of the connection is shut
-- down, and further writing is disallowed. Subsequent calls to
-- 'GI.Gio.Interfaces.DatagramBased.datagramBasedSendMessages' will return 'GI.Gio.Enums.IOErrorEnumClosed'.
-- 
-- It is allowed for both /@shutdownRead@/ and /@shutdownWrite@/ to be TRUE — this
-- is equivalent to calling 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionClose'.
-- 
-- If /@cancellable@/ is cancelled, the t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection' may be left
-- partially-closed and any pending untransmitted data may be lost. Call
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdown' again to complete closing the t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'.
-- 
-- /Since: 2.48/
dtlsConnectionShutdown ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Bool
    -- ^ /@shutdownRead@/: 'P.True' to stop reception of incoming datagrams
    -> Bool
    -- ^ /@shutdownWrite@/: 'P.True' to stop sending outgoing datagrams
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dtlsConnectionShutdown :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Bool -> Bool -> Maybe b -> m ()
dtlsConnectionShutdown a
conn Bool
shutdownRead Bool
shutdownWrite Maybe b
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    let shutdownRead' :: CInt
shutdownRead' = (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
shutdownRead
    let shutdownWrite' :: CInt
shutdownWrite' = (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
shutdownWrite
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
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 a. a -> IO a
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 DtlsConnection
-> CInt -> CInt -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_dtls_connection_shutdown Ptr DtlsConnection
conn' CInt
shutdownRead' CInt
shutdownWrite' 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionShutdownMethodInfo
instance (signature ~ (Bool -> Bool -> Maybe (b) -> m ()), MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod DtlsConnectionShutdownMethodInfo a signature where
    overloadedMethod = dtlsConnectionShutdown

instance O.OverloadedMethodInfo DtlsConnectionShutdownMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdown",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionShutdown"
        })


#endif

-- method DtlsConnection::shutdown_async
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shutdown_read"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to stop reception of incoming datagrams"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shutdown_write"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to stop sending outgoing datagrams"
--                 , 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 shutdown operation is complete"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 6
--           , 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_dtls_connection_shutdown_async" g_dtls_connection_shutdown_async :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    CInt ->                                 -- shutdown_read : TBasicType TBoolean
    CInt ->                                 -- shutdown_write : TBasicType TBoolean
    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 shut down part or all of the DTLS connection. See
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdown' for more information.
-- 
-- /Since: 2.48/
dtlsConnectionShutdownAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> Bool
    -- ^ /@shutdownRead@/: 'P.True' to stop reception of incoming datagrams
    -> Bool
    -- ^ /@shutdownWrite@/: 'P.True' to stop sending outgoing datagrams
    -> 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 shutdown operation is complete
    -> m ()
dtlsConnectionShutdownAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a
-> Bool
-> Bool
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
dtlsConnectionShutdownAsync a
conn Bool
shutdownRead Bool
shutdownWrite Int32
ioPriority Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    let shutdownRead' :: CInt
shutdownRead' = (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
shutdownRead
    let shutdownWrite' :: CInt
shutdownWrite' = (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
shutdownWrite
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 a. a -> IO a
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 DtlsConnection
-> CInt
-> CInt
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_dtls_connection_shutdown_async Ptr DtlsConnection
conn' CInt
shutdownRead' CInt
shutdownWrite' 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionShutdownAsyncMethodInfo
instance (signature ~ (Bool -> Bool -> Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod DtlsConnectionShutdownAsyncMethodInfo a signature where
    overloadedMethod = dtlsConnectionShutdownAsync

instance O.OverloadedMethodInfo DtlsConnectionShutdownAsyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdownAsync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionShutdownAsync"
        })


#endif

-- method DtlsConnection::shutdown_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DtlsConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDtlsConnection" , 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_dtls_connection_shutdown_finish" g_dtls_connection_shutdown_finish :: 
    Ptr DtlsConnection ->                   -- conn : TInterface (Name {namespace = "Gio", name = "DtlsConnection"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finish an asynchronous TLS shutdown operation. See
-- 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdown' for more information.
-- 
-- /Since: 2.48/
dtlsConnectionShutdownFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dtlsConnectionShutdownFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsAsyncResult b) =>
a -> b -> m ()
dtlsConnectionShutdownFinish a
conn b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DtlsConnection
conn' <- a -> IO (Ptr DtlsConnection)
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 DtlsConnection
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_dtls_connection_shutdown_finish Ptr DtlsConnection
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DtlsConnectionShutdownFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod DtlsConnectionShutdownFinishMethodInfo a signature where
    overloadedMethod = dtlsConnectionShutdownFinish

instance O.OverloadedMethodInfo DtlsConnectionShutdownFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdownFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionShutdownFinish"
        })


#endif

-- signal DtlsConnection::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.DtlsClientConnection.DtlsClientConnection':@/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'.
-- 
-- GLib guarantees that if certificate verification fails, this signal
-- will be emitted with at least one error will be set in /@errors@/, but
-- it does not guarantee that all possible errors will be set.
-- Accordingly, you may not safely decide to ignore any particular
-- type of error. For example, it would be incorrect to ignore
-- 'GI.Gio.Flags.TlsCertificateFlagsExpired' if you want to allow expired
-- certificates, because this could potentially be the only error flag
-- set even if other problems exist with the certificate.
-- 
-- 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.DtlsServerConnection.DtlsServerConnection':@/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.48/
type DtlsConnectionAcceptCertificateCallback =
    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_DtlsConnectionAcceptCertificateCallback =
    Ptr DtlsConnection ->                   -- object
    Ptr Gio.TlsCertificate.TlsCertificate ->
    CUInt ->
    Ptr () ->                               -- user_data
    IO CInt

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

wrap_DtlsConnectionAcceptCertificateCallback :: 
    GObject a => (a -> DtlsConnectionAcceptCertificateCallback) ->
    C_DtlsConnectionAcceptCertificateCallback
wrap_DtlsConnectionAcceptCertificateCallback :: forall a.
GObject a =>
(a -> DtlsConnectionAcceptCertificateCallback)
-> C_DtlsConnectionAcceptCertificateCallback
wrap_DtlsConnectionAcceptCertificateCallback a -> DtlsConnectionAcceptCertificateCallback
gi'cb Ptr DtlsConnection
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 DtlsConnection -> (DtlsConnection -> IO Bool) -> IO Bool
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr DtlsConnection
gi'selfPtr ((DtlsConnection -> IO Bool) -> IO Bool)
-> (DtlsConnection -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \DtlsConnection
gi'self -> a -> DtlsConnectionAcceptCertificateCallback
gi'cb (DtlsConnection -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DtlsConnection
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 a. a -> IO a
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' dtlsConnection #acceptCertificate callback
-- @
-- 
-- 
onDtlsConnectionAcceptCertificate :: (IsDtlsConnection a, MonadIO m) => a -> ((?self :: a) => DtlsConnectionAcceptCertificateCallback) -> m SignalHandlerId
onDtlsConnectionAcceptCertificate :: forall a (m :: * -> *).
(IsDtlsConnection a, MonadIO m) =>
a
-> ((?self::a) => DtlsConnectionAcceptCertificateCallback)
-> m SignalHandlerId
onDtlsConnectionAcceptCertificate a
obj (?self::a) => DtlsConnectionAcceptCertificateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 -> DtlsConnectionAcceptCertificateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DtlsConnectionAcceptCertificateCallback
DtlsConnectionAcceptCertificateCallback
cb
    let wrapped' :: C_DtlsConnectionAcceptCertificateCallback
wrapped' = (a -> DtlsConnectionAcceptCertificateCallback)
-> C_DtlsConnectionAcceptCertificateCallback
forall a.
GObject a =>
(a -> DtlsConnectionAcceptCertificateCallback)
-> C_DtlsConnectionAcceptCertificateCallback
wrap_DtlsConnectionAcceptCertificateCallback a -> DtlsConnectionAcceptCertificateCallback
wrapped
    FunPtr C_DtlsConnectionAcceptCertificateCallback
wrapped'' <- C_DtlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_DtlsConnectionAcceptCertificateCallback)
mk_DtlsConnectionAcceptCertificateCallback C_DtlsConnectionAcceptCertificateCallback
wrapped'
    a
-> Text
-> FunPtr C_DtlsConnectionAcceptCertificateCallback
-> 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_DtlsConnectionAcceptCertificateCallback
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' dtlsConnection #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.
-- 
afterDtlsConnectionAcceptCertificate :: (IsDtlsConnection a, MonadIO m) => a -> ((?self :: a) => DtlsConnectionAcceptCertificateCallback) -> m SignalHandlerId
afterDtlsConnectionAcceptCertificate :: forall a (m :: * -> *).
(IsDtlsConnection a, MonadIO m) =>
a
-> ((?self::a) => DtlsConnectionAcceptCertificateCallback)
-> m SignalHandlerId
afterDtlsConnectionAcceptCertificate a
obj (?self::a) => DtlsConnectionAcceptCertificateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 -> DtlsConnectionAcceptCertificateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DtlsConnectionAcceptCertificateCallback
DtlsConnectionAcceptCertificateCallback
cb
    let wrapped' :: C_DtlsConnectionAcceptCertificateCallback
wrapped' = (a -> DtlsConnectionAcceptCertificateCallback)
-> C_DtlsConnectionAcceptCertificateCallback
forall a.
GObject a =>
(a -> DtlsConnectionAcceptCertificateCallback)
-> C_DtlsConnectionAcceptCertificateCallback
wrap_DtlsConnectionAcceptCertificateCallback a -> DtlsConnectionAcceptCertificateCallback
wrapped
    FunPtr C_DtlsConnectionAcceptCertificateCallback
wrapped'' <- C_DtlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_DtlsConnectionAcceptCertificateCallback)
mk_DtlsConnectionAcceptCertificateCallback C_DtlsConnectionAcceptCertificateCallback
wrapped'
    a
-> Text
-> FunPtr C_DtlsConnectionAcceptCertificateCallback
-> 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_DtlsConnectionAcceptCertificateCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DtlsConnectionAcceptCertificateSignalInfo
instance SignalInfo DtlsConnectionAcceptCertificateSignalInfo where
    type HaskellCallbackType DtlsConnectionAcceptCertificateSignalInfo = DtlsConnectionAcceptCertificateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DtlsConnectionAcceptCertificateCallback cb
        cb'' <- mk_DtlsConnectionAcceptCertificateCallback cb'
        connectSignalFunPtr obj "accept-certificate" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DtlsConnection::accept-certificate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-DtlsConnection.html#g:signal:acceptCertificate"})

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DtlsConnection = DtlsConnectionSignalList
type DtlsConnectionSignalList = ('[ '("acceptCertificate", DtlsConnectionAcceptCertificateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif