{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.DtlsServerConnection
(
DtlsServerConnection(..) ,
noDtlsServerConnection ,
IsDtlsServerConnection ,
toDtlsServerConnection ,
#if defined(ENABLE_OVERLOADING)
ResolveDtlsServerConnectionMethod ,
#endif
dtlsServerConnectionNew ,
#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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.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
newtype DtlsServerConnection = DtlsServerConnection (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)
noDtlsServerConnection :: Maybe DtlsServerConnection
noDtlsServerConnection :: Maybe DtlsServerConnection
noDtlsServerConnection = Maybe DtlsServerConnection
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DtlsServerConnection = DtlsServerConnectionSignalList
type DtlsServerConnectionSignalList = ('[ '("acceptCertificate", Gio.DtlsConnection.DtlsConnectionAcceptCertificateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_dtls_server_connection_get_type"
c_g_dtls_server_connection_get_type :: IO GType
instance GObject DtlsServerConnection where
gobjectType :: IO GType
gobjectType = IO GType
c_g_dtls_server_connection_get_type
instance B.GValue.IsGValue DtlsServerConnection where
toGValue :: DtlsServerConnection -> IO GValue
toGValue o :: DtlsServerConnection
o = do
GType
gtype <- IO GType
c_g_dtls_server_connection_get_type
DtlsServerConnection
-> (Ptr DtlsServerConnection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DtlsServerConnection
o (GType
-> (GValue -> Ptr DtlsServerConnection -> IO ())
-> Ptr DtlsServerConnection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DtlsServerConnection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO DtlsServerConnection
fromGValue gv :: GValue
gv = do
Ptr DtlsServerConnection
ptr <- GValue -> IO (Ptr DtlsServerConnection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DtlsServerConnection)
(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
class (GObject o, O.IsDescendantOf DtlsServerConnection o) => IsDtlsServerConnection o
instance (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]
toDtlsServerConnection :: (MonadIO m, IsDtlsServerConnection o) => o -> m DtlsServerConnection
toDtlsServerConnection :: o -> m DtlsServerConnection
toDtlsServerConnection = IO DtlsServerConnection -> m DtlsServerConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DtlsServerConnection -> DtlsServerConnection
DtlsServerConnection
getDtlsServerConnectionAuthenticationMode :: (MonadIO m, IsDtlsServerConnection o) => o -> m Gio.Enums.TlsAuthenticationMode
getDtlsServerConnectionAuthenticationMode :: o -> m TlsAuthenticationMode
getDtlsServerConnectionAuthenticationMode obj :: o
obj = IO TlsAuthenticationMode -> m TlsAuthenticationMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "authentication-mode"
setDtlsServerConnectionAuthenticationMode :: (MonadIO m, IsDtlsServerConnection o) => o -> Gio.Enums.TlsAuthenticationMode -> m ()
setDtlsServerConnectionAuthenticationMode :: o -> TlsAuthenticationMode -> m ()
setDtlsServerConnectionAuthenticationMode obj :: o
obj val :: TlsAuthenticationMode
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> TlsAuthenticationMode -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj "authentication-mode" TlsAuthenticationMode
val
constructDtlsServerConnectionAuthenticationMode :: (IsDtlsServerConnection o) => Gio.Enums.TlsAuthenticationMode -> IO (GValueConstruct o)
constructDtlsServerConnectionAuthenticationMode :: TlsAuthenticationMode -> IO (GValueConstruct o)
constructDtlsServerConnectionAuthenticationMode val :: TlsAuthenticationMode
val = String -> TlsAuthenticationMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "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 "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.MethodInfo 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
#endif
foreign import ccall "g_dtls_server_connection_new" g_dtls_server_connection_new ::
Ptr Gio.DatagramBased.DatagramBased ->
Ptr Gio.TlsCertificate.TlsCertificate ->
Ptr (Ptr GError) ->
IO (Ptr DtlsServerConnection)
dtlsServerConnectionNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.DatagramBased.IsDatagramBased a, Gio.TlsCertificate.IsTlsCertificate b) =>
a
-> Maybe (b)
-> m DtlsServerConnection
dtlsServerConnectionNew :: a -> Maybe b -> m DtlsServerConnection
dtlsServerConnectionNew baseSocket :: a
baseSocket certificate :: 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
Nothing -> Ptr TlsCertificate -> IO (Ptr TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsCertificate
forall a. Ptr a
nullPtr
Just jCertificate :: 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 "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