{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Interfaces.DtlsServerConnection.DtlsServerConnection' is the server-side subclass of t'GI.Gio.Interfaces.DtlsConnection.DtlsConnection',
-- representing a server-side DTLS connection.
-- 
-- /Since: 2.48/

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

module GI.Gio.Interfaces.DtlsServerConnection
    ( 

-- * Exported types
    DtlsServerConnection(..)                ,
    IsDtlsServerConnection                  ,
    toDtlsServerConnection                  ,


 -- * 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"), [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"), [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)
    ResolveDtlsServerConnectionMethod       ,
#endif

-- ** new #method:new#

    dtlsServerConnectionNew                 ,




 -- * Properties


-- ** authenticationMode #attr:authenticationMode#
-- | The t'GI.Gio.Enums.TlsAuthenticationMode' for the server. This can be changed
-- before calling 'GI.Gio.Interfaces.DtlsConnection.dtlsConnectionHandshake' if you want to
-- rehandshake with a different mode from the initial handshake.
-- 
-- /Since: 2.48/

#if defined(ENABLE_OVERLOADING)
    DtlsServerConnectionAuthenticationModePropertyInfo,
#endif
    constructDtlsServerConnectionAuthenticationMode,
#if defined(ENABLE_OVERLOADING)
    dtlsServerConnectionAuthenticationMode  ,
#endif
    getDtlsServerConnectionAuthenticationMode,
    setDtlsServerConnectionAuthenticationMode,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.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 {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.DatagramBased as Gio.DatagramBased
import {-# SOURCE #-} qualified GI.Gio.Interfaces.DtlsConnection as Gio.DtlsConnection
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsCertificate as Gio.TlsCertificate

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

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

foreign import ccall "g_dtls_server_connection_get_type"
    c_g_dtls_server_connection_get_type :: IO B.Types.GType

instance B.Types.TypedObject DtlsServerConnection where
    glibType :: IO GType
glibType = IO GType
c_g_dtls_server_connection_get_type

instance B.Types.GObject DtlsServerConnection

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

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

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

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

-- VVV Prop "authentication-mode"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsAuthenticationMode"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@authentication-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dtlsServerConnection [ #authenticationMode 'Data.GI.Base.Attributes.:=' value ]
-- @
setDtlsServerConnectionAuthenticationMode :: (MonadIO m, IsDtlsServerConnection o) => o -> Gio.Enums.TlsAuthenticationMode -> m ()
setDtlsServerConnectionAuthenticationMode :: forall (m :: * -> *) o.
(MonadIO m, IsDtlsServerConnection o) =>
o -> TlsAuthenticationMode -> m ()
setDtlsServerConnectionAuthenticationMode o
obj TlsAuthenticationMode
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> TlsAuthenticationMode -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"authentication-mode" TlsAuthenticationMode
val

-- | Construct a `GValueConstruct` with valid value for the “@authentication-mode@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDtlsServerConnectionAuthenticationMode :: (IsDtlsServerConnection o, MIO.MonadIO m) => Gio.Enums.TlsAuthenticationMode -> m (GValueConstruct o)
constructDtlsServerConnectionAuthenticationMode :: forall o (m :: * -> *).
(IsDtlsServerConnection o, MonadIO m) =>
TlsAuthenticationMode -> m (GValueConstruct o)
constructDtlsServerConnectionAuthenticationMode TlsAuthenticationMode
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> TlsAuthenticationMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"authentication-mode" TlsAuthenticationMode
val

#if defined(ENABLE_OVERLOADING)
data DtlsServerConnectionAuthenticationModePropertyInfo
instance AttrInfo DtlsServerConnectionAuthenticationModePropertyInfo where
    type AttrAllowedOps DtlsServerConnectionAuthenticationModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DtlsServerConnectionAuthenticationModePropertyInfo = IsDtlsServerConnection
    type AttrSetTypeConstraint DtlsServerConnectionAuthenticationModePropertyInfo = (~) Gio.Enums.TlsAuthenticationMode
    type AttrTransferTypeConstraint DtlsServerConnectionAuthenticationModePropertyInfo = (~) Gio.Enums.TlsAuthenticationMode
    type AttrTransferType DtlsServerConnectionAuthenticationModePropertyInfo = Gio.Enums.TlsAuthenticationMode
    type AttrGetType DtlsServerConnectionAuthenticationModePropertyInfo = Gio.Enums.TlsAuthenticationMode
    type AttrLabel DtlsServerConnectionAuthenticationModePropertyInfo = "authentication-mode"
    type AttrOrigin DtlsServerConnectionAuthenticationModePropertyInfo = DtlsServerConnection
    attrGet = getDtlsServerConnectionAuthenticationMode
    attrSet = setDtlsServerConnectionAuthenticationMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructDtlsServerConnectionAuthenticationMode
    attrClear = undefined
#endif

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

#if defined(ENABLE_OVERLOADING)
dtlsServerConnectionAuthenticationMode :: AttrLabelProxy "authenticationMode"
dtlsServerConnectionAuthenticationMode = AttrLabelProxy

#endif

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

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

#endif

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

#endif

-- method DtlsServerConnection::new
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "base_socket"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DatagramBased" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GDatagramBased to wrap"
--                 , 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 = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the default server certificate, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "DtlsServerConnection" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dtls_server_connection_new" g_dtls_server_connection_new :: 
    Ptr Gio.DatagramBased.DatagramBased ->  -- base_socket : TInterface (Name {namespace = "Gio", name = "DatagramBased"})
    Ptr Gio.TlsCertificate.TlsCertificate -> -- certificate : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DtlsServerConnection)

-- | Creates a new t'GI.Gio.Interfaces.DtlsServerConnection.DtlsServerConnection' wrapping /@baseSocket@/.
-- 
-- /Since: 2.48/
dtlsServerConnectionNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.DatagramBased.IsDatagramBased a, Gio.TlsCertificate.IsTlsCertificate b) =>
    a
    -- ^ /@baseSocket@/: the t'GI.Gio.Interfaces.DatagramBased.DatagramBased' to wrap
    -> Maybe (b)
    -- ^ /@certificate@/: the default server certificate, or 'P.Nothing'
    -> m DtlsServerConnection
    -- ^ __Returns:__ the new
    --   t'GI.Gio.Interfaces.DtlsServerConnection.DtlsServerConnection', or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
dtlsServerConnectionNew :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDatagramBased a, IsTlsCertificate b) =>
a -> Maybe b -> m DtlsServerConnection
dtlsServerConnectionNew a
baseSocket Maybe b
certificate = IO DtlsServerConnection -> m DtlsServerConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DtlsServerConnection -> m DtlsServerConnection)
-> IO DtlsServerConnection -> m DtlsServerConnection
forall a b. (a -> b) -> a -> b
$ do
    Ptr DatagramBased
baseSocket' <- a -> IO (Ptr DatagramBased)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
baseSocket
    Ptr TlsCertificate
maybeCertificate <- case Maybe b
certificate of
        Maybe b
Nothing -> Ptr TlsCertificate -> IO (Ptr TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsCertificate
forall a. Ptr a
nullPtr
        Just b
jCertificate -> do
            Ptr TlsCertificate
jCertificate' <- b -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCertificate
            Ptr TlsCertificate -> IO (Ptr TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsCertificate
jCertificate'
    IO DtlsServerConnection -> IO () -> IO DtlsServerConnection
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DtlsServerConnection
result <- (Ptr (Ptr GError) -> IO (Ptr DtlsServerConnection))
-> IO (Ptr DtlsServerConnection)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DtlsServerConnection))
 -> IO (Ptr DtlsServerConnection))
-> (Ptr (Ptr GError) -> IO (Ptr DtlsServerConnection))
-> IO (Ptr DtlsServerConnection)
forall a b. (a -> b) -> a -> b
$ Ptr DatagramBased
-> Ptr TlsCertificate
-> Ptr (Ptr GError)
-> IO (Ptr DtlsServerConnection)
g_dtls_server_connection_new Ptr DatagramBased
baseSocket' Ptr TlsCertificate
maybeCertificate
        Text -> Ptr DtlsServerConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dtlsServerConnectionNew" Ptr DtlsServerConnection
result
        DtlsServerConnection
result' <- ((ManagedPtr DtlsServerConnection -> DtlsServerConnection)
-> Ptr DtlsServerConnection -> IO DtlsServerConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DtlsServerConnection -> DtlsServerConnection
DtlsServerConnection) Ptr DtlsServerConnection
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
baseSocket
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
certificate b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        DtlsServerConnection -> IO DtlsServerConnection
forall (m :: * -> *) a. Monad m => a -> m a
return DtlsServerConnection
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif