{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.DtlsConnection
(
DtlsConnection(..) ,
IsDtlsConnection ,
toDtlsConnection ,
#if defined(ENABLE_OVERLOADING)
ResolveDtlsConnectionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DtlsConnectionCloseMethodInfo ,
#endif
dtlsConnectionClose ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionCloseAsyncMethodInfo ,
#endif
dtlsConnectionCloseAsync ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionCloseFinishMethodInfo ,
#endif
dtlsConnectionCloseFinish ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionEmitAcceptCertificateMethodInfo,
#endif
dtlsConnectionEmitAcceptCertificate ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetCertificateMethodInfo ,
#endif
dtlsConnectionGetCertificate ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetChannelBindingDataMethodInfo,
#endif
dtlsConnectionGetChannelBindingData ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetCiphersuiteNameMethodInfo,
#endif
dtlsConnectionGetCiphersuiteName ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetDatabaseMethodInfo ,
#endif
dtlsConnectionGetDatabase ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetInteractionMethodInfo ,
#endif
dtlsConnectionGetInteraction ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetNegotiatedProtocolMethodInfo,
#endif
dtlsConnectionGetNegotiatedProtocol ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetPeerCertificateMethodInfo,
#endif
dtlsConnectionGetPeerCertificate ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetPeerCertificateErrorsMethodInfo,
#endif
dtlsConnectionGetPeerCertificateErrors ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetProtocolVersionMethodInfo,
#endif
dtlsConnectionGetProtocolVersion ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetRehandshakeModeMethodInfo,
#endif
dtlsConnectionGetRehandshakeMode ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionGetRequireCloseNotifyMethodInfo,
#endif
dtlsConnectionGetRequireCloseNotify ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionHandshakeMethodInfo ,
#endif
dtlsConnectionHandshake ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionHandshakeAsyncMethodInfo ,
#endif
dtlsConnectionHandshakeAsync ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionHandshakeFinishMethodInfo ,
#endif
dtlsConnectionHandshakeFinish ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionSetAdvertisedProtocolsMethodInfo,
#endif
dtlsConnectionSetAdvertisedProtocols ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionSetCertificateMethodInfo ,
#endif
dtlsConnectionSetCertificate ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionSetDatabaseMethodInfo ,
#endif
dtlsConnectionSetDatabase ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionSetInteractionMethodInfo ,
#endif
dtlsConnectionSetInteraction ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionSetRehandshakeModeMethodInfo,
#endif
dtlsConnectionSetRehandshakeMode ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionSetRequireCloseNotifyMethodInfo,
#endif
dtlsConnectionSetRequireCloseNotify ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionShutdownMethodInfo ,
#endif
dtlsConnectionShutdown ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionShutdownAsyncMethodInfo ,
#endif
dtlsConnectionShutdownAsync ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionShutdownFinishMethodInfo ,
#endif
dtlsConnectionShutdownFinish ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionAdvertisedProtocolsPropertyInfo,
#endif
clearDtlsConnectionAdvertisedProtocols ,
constructDtlsConnectionAdvertisedProtocols,
#if defined(ENABLE_OVERLOADING)
dtlsConnectionAdvertisedProtocols ,
#endif
getDtlsConnectionAdvertisedProtocols ,
setDtlsConnectionAdvertisedProtocols ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionBaseSocketPropertyInfo ,
#endif
constructDtlsConnectionBaseSocket ,
#if defined(ENABLE_OVERLOADING)
dtlsConnectionBaseSocket ,
#endif
getDtlsConnectionBaseSocket ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionCertificatePropertyInfo ,
#endif
constructDtlsConnectionCertificate ,
#if defined(ENABLE_OVERLOADING)
dtlsConnectionCertificate ,
#endif
getDtlsConnectionCertificate ,
setDtlsConnectionCertificate ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionCiphersuiteNamePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
dtlsConnectionCiphersuiteName ,
#endif
getDtlsConnectionCiphersuiteName ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionDatabasePropertyInfo ,
#endif
clearDtlsConnectionDatabase ,
constructDtlsConnectionDatabase ,
#if defined(ENABLE_OVERLOADING)
dtlsConnectionDatabase ,
#endif
getDtlsConnectionDatabase ,
setDtlsConnectionDatabase ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionInteractionPropertyInfo ,
#endif
clearDtlsConnectionInteraction ,
constructDtlsConnectionInteraction ,
#if defined(ENABLE_OVERLOADING)
dtlsConnectionInteraction ,
#endif
getDtlsConnectionInteraction ,
setDtlsConnectionInteraction ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionNegotiatedProtocolPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
dtlsConnectionNegotiatedProtocol ,
#endif
getDtlsConnectionNegotiatedProtocol ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionPeerCertificatePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
dtlsConnectionPeerCertificate ,
#endif
getDtlsConnectionPeerCertificate ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionPeerCertificateErrorsPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
dtlsConnectionPeerCertificateErrors ,
#endif
getDtlsConnectionPeerCertificateErrors ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionProtocolVersionPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
dtlsConnectionProtocolVersion ,
#endif
getDtlsConnectionProtocolVersion ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionRehandshakeModePropertyInfo,
#endif
constructDtlsConnectionRehandshakeMode ,
#if defined(ENABLE_OVERLOADING)
dtlsConnectionRehandshakeMode ,
#endif
getDtlsConnectionRehandshakeMode ,
setDtlsConnectionRehandshakeMode ,
#if defined(ENABLE_OVERLOADING)
DtlsConnectionRequireCloseNotifyPropertyInfo,
#endif
constructDtlsConnectionRequireCloseNotify,
#if defined(ENABLE_OVERLOADING)
dtlsConnectionRequireCloseNotify ,
#endif
getDtlsConnectionRequireCloseNotify ,
setDtlsConnectionRequireCloseNotify ,
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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Flags as GLib.Flags
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GObject.Callbacks as GObject.Callbacks
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.Interfaces.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.InetAddress as Gio.InetAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddressEnumerator as Gio.SocketAddressEnumerator
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsCertificate as Gio.TlsCertificate
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsConnection as Gio.TlsConnection
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsDatabase as Gio.TlsDatabase
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsInteraction as Gio.TlsInteraction
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsPassword as Gio.TlsPassword
import {-# SOURCE #-} qualified GI.Gio.Structs.InputMessage as Gio.InputMessage
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputMessage as Gio.OutputMessage
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector
#else
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
#endif
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
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]
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
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 <- 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 /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject DtlsConnection ptr
else return P.Nothing
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"
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)
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)
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 :: forall o.
AttrBaseTypeConstraint
DtlsConnectionAdvertisedProtocolsPropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionAdvertisedProtocolsPropertyInfo)
attrGet = o -> IO (Maybe [Text])
o -> IO (AttrGetType DtlsConnectionAdvertisedProtocolsPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe [Text])
getDtlsConnectionAdvertisedProtocols
attrSet :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionAdvertisedProtocolsPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionAdvertisedProtocolsPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
o -> [Text] -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> [Text] -> m ()
setDtlsConnectionAdvertisedProtocols
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionAdvertisedProtocolsPropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionAdvertisedProtocolsPropertyInfo b) =>
Proxy o
-> b
-> IO
(AttrTransferType DtlsConnectionAdvertisedProtocolsPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionAdvertisedProtocolsPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionAdvertisedProtocolsPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
[Text] -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsDtlsConnection o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructDtlsConnectionAdvertisedProtocols
attrClear :: forall o.
AttrBaseTypeConstraint
DtlsConnectionAdvertisedProtocolsPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m ()
clearDtlsConnectionAdvertisedProtocols
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.advertisedProtocols"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:advertisedProtocols"
})
#endif
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
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 :: forall o.
AttrBaseTypeConstraint DtlsConnectionBaseSocketPropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionBaseSocketPropertyInfo)
attrGet = o -> IO (Maybe DatagramBased)
o -> IO (AttrGetType DtlsConnectionBaseSocketPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe DatagramBased)
getDtlsConnectionBaseSocket
attrSet :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionBaseSocketPropertyInfo o,
AttrSetTypeConstraint DtlsConnectionBaseSocketPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionBaseSocketPropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionBaseSocketPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType DtlsConnectionBaseSocketPropertyInfo)
attrTransfer Proxy o
_ b
v = do
(ManagedPtr DatagramBased -> DatagramBased)
-> b -> IO DatagramBased
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DatagramBased -> DatagramBased
Gio.DatagramBased.DatagramBased b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionBaseSocketPropertyInfo o,
AttrSetTypeConstraint DtlsConnectionBaseSocketPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall o (m :: * -> *) a.
(IsDtlsConnection o, MonadIO m, IsDatagramBased a) =>
a -> m (GValueConstruct o)
constructDtlsConnectionBaseSocket
attrClear :: forall o.
AttrBaseTypeConstraint DtlsConnectionBaseSocketPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.baseSocket"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:baseSocket"
})
#endif
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
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)
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 :: forall o.
AttrBaseTypeConstraint DtlsConnectionCertificatePropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionCertificatePropertyInfo)
attrGet = o -> IO (Maybe TlsCertificate)
o -> IO (AttrGetType DtlsConnectionCertificatePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe TlsCertificate)
getDtlsConnectionCertificate
attrSet :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionCertificatePropertyInfo o,
AttrSetTypeConstraint DtlsConnectionCertificatePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall (m :: * -> *) o a.
(MonadIO m, IsDtlsConnection o, IsTlsCertificate a) =>
o -> a -> m ()
setDtlsConnectionCertificate
attrTransfer :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionCertificatePropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionCertificatePropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType DtlsConnectionCertificatePropertyInfo)
attrTransfer Proxy o
_ b
v = do
(ManagedPtr TlsCertificate -> TlsCertificate)
-> b -> IO TlsCertificate
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TlsCertificate -> TlsCertificate
Gio.TlsCertificate.TlsCertificate b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionCertificatePropertyInfo o,
AttrSetTypeConstraint DtlsConnectionCertificatePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall o (m :: * -> *) a.
(IsDtlsConnection o, MonadIO m, IsTlsCertificate a) =>
a -> m (GValueConstruct o)
constructDtlsConnectionCertificate
attrClear :: forall o.
AttrBaseTypeConstraint DtlsConnectionCertificatePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.certificate"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:certificate"
})
#endif
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 :: forall o.
AttrBaseTypeConstraint
DtlsConnectionCiphersuiteNamePropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionCiphersuiteNamePropertyInfo)
attrGet = o -> IO (Maybe Text)
o -> IO (AttrGetType DtlsConnectionCiphersuiteNamePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe Text)
getDtlsConnectionCiphersuiteName
attrSet :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionCiphersuiteNamePropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionCiphersuiteNamePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionCiphersuiteNamePropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionCiphersuiteNamePropertyInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType DtlsConnectionCiphersuiteNamePropertyInfo)
attrTransfer Proxy o
_ = b
-> IO (AttrTransferType DtlsConnectionCiphersuiteNamePropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionCiphersuiteNamePropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionCiphersuiteNamePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint
DtlsConnectionCiphersuiteNamePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.ciphersuiteName"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:ciphersuiteName"
})
#endif
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
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)
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)
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 :: forall o.
AttrBaseTypeConstraint DtlsConnectionDatabasePropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionDatabasePropertyInfo)
attrGet = o -> IO (Maybe TlsDatabase)
o -> IO (AttrGetType DtlsConnectionDatabasePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe TlsDatabase)
getDtlsConnectionDatabase
attrSet :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionDatabasePropertyInfo o,
AttrSetTypeConstraint DtlsConnectionDatabasePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall (m :: * -> *) o a.
(MonadIO m, IsDtlsConnection o, IsTlsDatabase a) =>
o -> a -> m ()
setDtlsConnectionDatabase
attrTransfer :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionDatabasePropertyInfo o,
AttrTransferTypeConstraint DtlsConnectionDatabasePropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType DtlsConnectionDatabasePropertyInfo)
attrTransfer Proxy o
_ b
v = do
(ManagedPtr TlsDatabase -> TlsDatabase) -> b -> IO TlsDatabase
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TlsDatabase -> TlsDatabase
Gio.TlsDatabase.TlsDatabase b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionDatabasePropertyInfo o,
AttrSetTypeConstraint DtlsConnectionDatabasePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall o (m :: * -> *) a.
(IsDtlsConnection o, MonadIO m, IsTlsDatabase a) =>
a -> m (GValueConstruct o)
constructDtlsConnectionDatabase
attrClear :: forall o.
AttrBaseTypeConstraint DtlsConnectionDatabasePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m ()
clearDtlsConnectionDatabase
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.database"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:database"
})
#endif
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
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)
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)
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 :: forall o.
AttrBaseTypeConstraint DtlsConnectionInteractionPropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionInteractionPropertyInfo)
attrGet = o -> IO (Maybe TlsInteraction)
o -> IO (AttrGetType DtlsConnectionInteractionPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe TlsInteraction)
getDtlsConnectionInteraction
attrSet :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionInteractionPropertyInfo o,
AttrSetTypeConstraint DtlsConnectionInteractionPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall (m :: * -> *) o a.
(MonadIO m, IsDtlsConnection o, IsTlsInteraction a) =>
o -> a -> m ()
setDtlsConnectionInteraction
attrTransfer :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionInteractionPropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionInteractionPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType DtlsConnectionInteractionPropertyInfo)
attrTransfer Proxy o
_ b
v = do
(ManagedPtr TlsInteraction -> TlsInteraction)
-> b -> IO TlsInteraction
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TlsInteraction -> TlsInteraction
Gio.TlsInteraction.TlsInteraction b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint DtlsConnectionInteractionPropertyInfo o,
AttrSetTypeConstraint DtlsConnectionInteractionPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall o (m :: * -> *) a.
(IsDtlsConnection o, MonadIO m, IsTlsInteraction a) =>
a -> m (GValueConstruct o)
constructDtlsConnectionInteraction
attrClear :: forall o.
AttrBaseTypeConstraint DtlsConnectionInteractionPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m ()
clearDtlsConnectionInteraction
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.interaction"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:interaction"
})
#endif
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 :: forall o.
AttrBaseTypeConstraint
DtlsConnectionNegotiatedProtocolPropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionNegotiatedProtocolPropertyInfo)
attrGet = o -> IO (Maybe Text)
o -> IO (AttrGetType DtlsConnectionNegotiatedProtocolPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe Text)
getDtlsConnectionNegotiatedProtocol
attrSet :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionNegotiatedProtocolPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionNegotiatedProtocolPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionNegotiatedProtocolPropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionNegotiatedProtocolPropertyInfo b) =>
Proxy o
-> b
-> IO
(AttrTransferType DtlsConnectionNegotiatedProtocolPropertyInfo)
attrTransfer Proxy o
_ = b
-> IO
(AttrTransferType DtlsConnectionNegotiatedProtocolPropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionNegotiatedProtocolPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionNegotiatedProtocolPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint
DtlsConnectionNegotiatedProtocolPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.negotiatedProtocol"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:negotiatedProtocol"
})
#endif
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 :: forall o.
AttrBaseTypeConstraint
DtlsConnectionPeerCertificatePropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionPeerCertificatePropertyInfo)
attrGet = o -> IO (Maybe TlsCertificate)
o -> IO (AttrGetType DtlsConnectionPeerCertificatePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m (Maybe TlsCertificate)
getDtlsConnectionPeerCertificate
attrSet :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionPeerCertificatePropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionPeerCertificatePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionPeerCertificatePropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionPeerCertificatePropertyInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType DtlsConnectionPeerCertificatePropertyInfo)
attrTransfer Proxy o
_ = b
-> IO (AttrTransferType DtlsConnectionPeerCertificatePropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionPeerCertificatePropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionPeerCertificatePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint
DtlsConnectionPeerCertificatePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.peerCertificate"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:peerCertificate"
})
#endif
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 :: forall o.
AttrBaseTypeConstraint
DtlsConnectionPeerCertificateErrorsPropertyInfo o =>
o
-> IO (AttrGetType DtlsConnectionPeerCertificateErrorsPropertyInfo)
attrGet = o -> IO [TlsCertificateFlags]
o
-> IO (AttrGetType DtlsConnectionPeerCertificateErrorsPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m [TlsCertificateFlags]
getDtlsConnectionPeerCertificateErrors
attrSet :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionPeerCertificateErrorsPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionPeerCertificateErrorsPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionPeerCertificateErrorsPropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionPeerCertificateErrorsPropertyInfo b) =>
Proxy o
-> b
-> IO
(AttrTransferType DtlsConnectionPeerCertificateErrorsPropertyInfo)
attrTransfer Proxy o
_ = b
-> IO
(AttrTransferType DtlsConnectionPeerCertificateErrorsPropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionPeerCertificateErrorsPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionPeerCertificateErrorsPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint
DtlsConnectionPeerCertificateErrorsPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.peerCertificateErrors"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:peerCertificateErrors"
})
#endif
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 :: forall o.
AttrBaseTypeConstraint
DtlsConnectionProtocolVersionPropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionProtocolVersionPropertyInfo)
attrGet = o -> IO (AttrGetType DtlsConnectionProtocolVersionPropertyInfo)
o -> IO TlsProtocolVersion
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m TlsProtocolVersion
getDtlsConnectionProtocolVersion
attrSet :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionProtocolVersionPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionProtocolVersionPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionProtocolVersionPropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionProtocolVersionPropertyInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType DtlsConnectionProtocolVersionPropertyInfo)
attrTransfer Proxy o
_ = b
-> IO (AttrTransferType DtlsConnectionProtocolVersionPropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionProtocolVersionPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionProtocolVersionPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint
DtlsConnectionProtocolVersionPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.protocolVersion"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:protocolVersion"
})
#endif
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"
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
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 :: forall o.
AttrBaseTypeConstraint
DtlsConnectionRehandshakeModePropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionRehandshakeModePropertyInfo)
attrGet = o -> IO (AttrGetType DtlsConnectionRehandshakeModePropertyInfo)
o -> IO TlsRehandshakeMode
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m TlsRehandshakeMode
getDtlsConnectionRehandshakeMode
attrSet :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionRehandshakeModePropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionRehandshakeModePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
o -> TlsRehandshakeMode -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> TlsRehandshakeMode -> m ()
setDtlsConnectionRehandshakeMode
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionRehandshakeModePropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionRehandshakeModePropertyInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType DtlsConnectionRehandshakeModePropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionRehandshakeModePropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionRehandshakeModePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
TlsRehandshakeMode -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsDtlsConnection o, MonadIO m) =>
TlsRehandshakeMode -> m (GValueConstruct o)
constructDtlsConnectionRehandshakeMode
attrClear :: forall o.
AttrBaseTypeConstraint
DtlsConnectionRehandshakeModePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.rehandshakeMode"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#g:attr:rehandshakeMode"
})
#endif
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"
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
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 :: forall o.
AttrBaseTypeConstraint
DtlsConnectionRequireCloseNotifyPropertyInfo o =>
o -> IO (AttrGetType DtlsConnectionRequireCloseNotifyPropertyInfo)
attrGet = o -> IO Bool
o -> IO (AttrGetType DtlsConnectionRequireCloseNotifyPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> m Bool
getDtlsConnectionRequireCloseNotify
attrSet :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionRequireCloseNotifyPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionRequireCloseNotifyPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
o -> Bool -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsDtlsConnection o) =>
o -> Bool -> m ()
setDtlsConnectionRequireCloseNotify
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionRequireCloseNotifyPropertyInfo o,
AttrTransferTypeConstraint
DtlsConnectionRequireCloseNotifyPropertyInfo b) =>
Proxy o
-> b
-> IO
(AttrTransferType DtlsConnectionRequireCloseNotifyPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
DtlsConnectionRequireCloseNotifyPropertyInfo o,
AttrSetTypeConstraint
DtlsConnectionRequireCloseNotifyPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Bool -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsDtlsConnection o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDtlsConnectionRequireCloseNotify
attrClear :: forall o.
AttrBaseTypeConstraint
DtlsConnectionRequireCloseNotifyPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.requireCloseNotify"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
dtlsConnectionAdvertisedProtocols :: AttrLabelProxy "advertisedProtocols"
dtlsConnectionAdvertisedProtocols :: AttrLabelProxy "advertisedProtocols"
dtlsConnectionAdvertisedProtocols = AttrLabelProxy "advertisedProtocols"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionBaseSocket :: AttrLabelProxy "baseSocket"
dtlsConnectionBaseSocket :: AttrLabelProxy "baseSocket"
dtlsConnectionBaseSocket = AttrLabelProxy "baseSocket"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionCertificate :: AttrLabelProxy "certificate"
dtlsConnectionCertificate :: AttrLabelProxy "certificate"
dtlsConnectionCertificate = AttrLabelProxy "certificate"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionCiphersuiteName :: AttrLabelProxy "ciphersuiteName"
dtlsConnectionCiphersuiteName :: AttrLabelProxy "ciphersuiteName"
dtlsConnectionCiphersuiteName = AttrLabelProxy "ciphersuiteName"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionDatabase :: AttrLabelProxy "database"
dtlsConnectionDatabase :: AttrLabelProxy "database"
dtlsConnectionDatabase = AttrLabelProxy "database"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionInteraction :: AttrLabelProxy "interaction"
dtlsConnectionInteraction :: AttrLabelProxy "interaction"
dtlsConnectionInteraction = AttrLabelProxy "interaction"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionNegotiatedProtocol :: AttrLabelProxy "negotiatedProtocol"
dtlsConnectionNegotiatedProtocol :: AttrLabelProxy "negotiatedProtocol"
dtlsConnectionNegotiatedProtocol = AttrLabelProxy "negotiatedProtocol"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionPeerCertificate :: AttrLabelProxy "peerCertificate"
dtlsConnectionPeerCertificate :: AttrLabelProxy "peerCertificate"
dtlsConnectionPeerCertificate = AttrLabelProxy "peerCertificate"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionPeerCertificateErrors :: AttrLabelProxy "peerCertificateErrors"
dtlsConnectionPeerCertificateErrors :: AttrLabelProxy "peerCertificateErrors"
dtlsConnectionPeerCertificateErrors = AttrLabelProxy "peerCertificateErrors"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionProtocolVersion :: AttrLabelProxy "protocolVersion"
dtlsConnectionProtocolVersion :: AttrLabelProxy "protocolVersion"
dtlsConnectionProtocolVersion = AttrLabelProxy "protocolVersion"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionRehandshakeMode :: AttrLabelProxy "rehandshakeMode"
dtlsConnectionRehandshakeMode :: AttrLabelProxy "rehandshakeMode"
dtlsConnectionRehandshakeMode = AttrLabelProxy "rehandshakeMode"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
dtlsConnectionRequireCloseNotify :: AttrLabelProxy "requireCloseNotify"
dtlsConnectionRequireCloseNotify :: AttrLabelProxy "requireCloseNotify"
dtlsConnectionRequireCloseNotify = AttrLabelProxy "requireCloseNotify"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveDtlsConnectionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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 :: DtlsConnection -> p
fromLabel = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
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 :: DtlsConnection -> p
getField = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
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 :: MethodProxy info DtlsConnection
fromLabel = MethodProxy info DtlsConnection
forall info obj. MethodProxy info obj
O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "g_dtls_connection_close" g_dtls_connection_close ::
Ptr DtlsConnection ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
dtlsConnectionClose ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m ()
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
maybeCancellable <- case 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
FP.nullPtr
Just b
jCancellable -> do
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
return jCancellable'
onException (do
_ <- propagateGError $ g_dtls_connection_close conn' maybeCancellable
touchManagedPtr conn
whenJust cancellable touchManagedPtr
return ()
) (do
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 :: a -> signature
overloadedMethod = a -> signature
a -> Maybe b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Maybe b -> m ()
dtlsConnectionClose
instance O.OverloadedMethodInfo DtlsConnectionCloseMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionClose",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionClose"
})
#endif
foreign import ccall "g_dtls_connection_close_async" g_dtls_connection_close_async ::
Ptr DtlsConnection ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
dtlsConnectionCloseAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
a
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
maybeCancellable <- case 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
FP.nullPtr
Just b
jCancellable -> do
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
return jCancellable'
maybeCallback <- case 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 FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
poke ptrcallback jCallback'
return jCallback'
let userData = Ptr a
forall a. Ptr a
nullPtr
g_dtls_connection_close_async conn' ioPriority maybeCancellable maybeCallback userData
touchManagedPtr conn
whenJust cancellable touchManagedPtr
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 :: a -> signature
overloadedMethod = a -> signature
a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
dtlsConnectionCloseAsync
instance O.OverloadedMethodInfo DtlsConnectionCloseAsyncMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionCloseAsync",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionCloseAsync"
})
#endif
foreign import ccall "g_dtls_connection_close_finish" g_dtls_connection_close_finish ::
Ptr DtlsConnection ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
dtlsConnectionCloseFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result_' <- unsafeManagedPtrCastPtr result_
onException (do
_ <- propagateGError $ g_dtls_connection_close_finish conn' result_'
touchManagedPtr conn
touchManagedPtr result_
return ()
) (do
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 :: a -> signature
overloadedMethod = a -> signature
a -> b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsAsyncResult b) =>
a -> b -> m ()
dtlsConnectionCloseFinish
instance O.OverloadedMethodInfo DtlsConnectionCloseFinishMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionCloseFinish",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionCloseFinish"
})
#endif
foreign import ccall "g_dtls_connection_emit_accept_certificate" g_dtls_connection_emit_accept_certificate ::
Ptr DtlsConnection ->
Ptr Gio.TlsCertificate.TlsCertificate ->
CUInt ->
IO CInt
dtlsConnectionEmitAcceptCertificate ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) =>
a
-> b
-> [Gio.Flags.TlsCertificateFlags]
-> m Bool
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
peerCert' <- unsafeManagedPtrCastPtr peerCert
let errors' = [TlsCertificateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TlsCertificateFlags]
errors
result <- g_dtls_connection_emit_accept_certificate conn' peerCert' errors'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr conn
touchManagedPtr peerCert
return 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 :: a -> signature
overloadedMethod = a -> signature
a -> b -> [TlsCertificateFlags] -> m Bool
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a,
IsTlsCertificate b) =>
a -> b -> [TlsCertificateFlags] -> m Bool
dtlsConnectionEmitAcceptCertificate
instance O.OverloadedMethodInfo DtlsConnectionEmitAcceptCertificateMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionEmitAcceptCertificate",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionEmitAcceptCertificate"
})
#endif
foreign import ccall "g_dtls_connection_get_certificate" g_dtls_connection_get_certificate ::
Ptr DtlsConnection ->
IO (Ptr Gio.TlsCertificate.TlsCertificate)
dtlsConnectionGetCertificate ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m (Maybe Gio.TlsCertificate.TlsCertificate)
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_certificate conn'
maybeResult <- convertIfNonNull result $ \Ptr TlsCertificate
result' -> do
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'
return result''
touchManagedPtr conn
return 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 :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe TlsCertificate)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe TlsCertificate)
dtlsConnectionGetCertificate
instance O.OverloadedMethodInfo DtlsConnectionGetCertificateMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetCertificate",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetCertificate"
})
#endif
foreign import ccall "g_dtls_connection_get_channel_binding_data" g_dtls_connection_get_channel_binding_data ::
Ptr DtlsConnection ->
CUInt ->
Ptr (Ptr GByteArray) ->
Ptr (Ptr GError) ->
IO CInt
dtlsConnectionGetChannelBindingData ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> Gio.Enums.TlsChannelBindingType
-> m (ByteString)
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let 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_
data_ <- callocMem :: IO (Ptr (Ptr GByteArray))
onException (do
_ <- propagateGError $ g_dtls_connection_get_channel_binding_data conn' type_' data_
data_' <- peek data_
data_'' <- unpackGByteArray data_'
touchManagedPtr conn
freeMem data_
return data_''
) (do
freeMem 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 :: a -> signature
overloadedMethod = a -> signature
a -> TlsChannelBindingType -> m ByteString
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> TlsChannelBindingType -> m ByteString
dtlsConnectionGetChannelBindingData
instance O.OverloadedMethodInfo DtlsConnectionGetChannelBindingDataMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetChannelBindingData",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetChannelBindingData"
})
#endif
foreign import ccall "g_dtls_connection_get_ciphersuite_name" g_dtls_connection_get_ciphersuite_name ::
Ptr DtlsConnection ->
IO CString
dtlsConnectionGetCiphersuiteName ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m (Maybe T.Text)
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_ciphersuite_name conn'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
freeMem result'
return result''
touchManagedPtr conn
return maybeResult
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetCiphersuiteNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetCiphersuiteNameMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe Text)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe Text)
dtlsConnectionGetCiphersuiteName
instance O.OverloadedMethodInfo DtlsConnectionGetCiphersuiteNameMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetCiphersuiteName",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetCiphersuiteName"
})
#endif
foreign import ccall "g_dtls_connection_get_database" g_dtls_connection_get_database ::
Ptr DtlsConnection ->
IO (Ptr Gio.TlsDatabase.TlsDatabase)
dtlsConnectionGetDatabase ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m (Maybe Gio.TlsDatabase.TlsDatabase)
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_database conn'
maybeResult <- convertIfNonNull result $ \Ptr TlsDatabase
result' -> do
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'
return result''
touchManagedPtr conn
return 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 :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe TlsDatabase)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe TlsDatabase)
dtlsConnectionGetDatabase
instance O.OverloadedMethodInfo DtlsConnectionGetDatabaseMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetDatabase",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetDatabase"
})
#endif
foreign import ccall "g_dtls_connection_get_interaction" g_dtls_connection_get_interaction ::
Ptr DtlsConnection ->
IO (Ptr Gio.TlsInteraction.TlsInteraction)
dtlsConnectionGetInteraction ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m (Maybe Gio.TlsInteraction.TlsInteraction)
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_interaction conn'
maybeResult <- convertIfNonNull result $ \Ptr TlsInteraction
result' -> do
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'
return result''
touchManagedPtr conn
return 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 :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe TlsInteraction)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe TlsInteraction)
dtlsConnectionGetInteraction
instance O.OverloadedMethodInfo DtlsConnectionGetInteractionMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetInteraction",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetInteraction"
})
#endif
foreign import ccall "g_dtls_connection_get_negotiated_protocol" g_dtls_connection_get_negotiated_protocol ::
Ptr DtlsConnection ->
IO CString
dtlsConnectionGetNegotiatedProtocol ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m (Maybe T.Text)
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_negotiated_protocol conn'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
return result''
touchManagedPtr conn
return maybeResult
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetNegotiatedProtocolMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetNegotiatedProtocolMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe Text)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe Text)
dtlsConnectionGetNegotiatedProtocol
instance O.OverloadedMethodInfo DtlsConnectionGetNegotiatedProtocolMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetNegotiatedProtocol",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetNegotiatedProtocol"
})
#endif
foreign import ccall "g_dtls_connection_get_peer_certificate" g_dtls_connection_get_peer_certificate ::
Ptr DtlsConnection ->
IO (Ptr Gio.TlsCertificate.TlsCertificate)
dtlsConnectionGetPeerCertificate ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m (Maybe Gio.TlsCertificate.TlsCertificate)
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_peer_certificate conn'
maybeResult <- convertIfNonNull result $ \Ptr TlsCertificate
result' -> do
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'
return result''
touchManagedPtr conn
return 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 :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe TlsCertificate)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m (Maybe TlsCertificate)
dtlsConnectionGetPeerCertificate
instance O.OverloadedMethodInfo DtlsConnectionGetPeerCertificateMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetPeerCertificate",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetPeerCertificate"
})
#endif
foreign import ccall "g_dtls_connection_get_peer_certificate_errors" g_dtls_connection_get_peer_certificate_errors ::
Ptr DtlsConnection ->
IO CUInt
dtlsConnectionGetPeerCertificateErrors ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m [Gio.Flags.TlsCertificateFlags]
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_peer_certificate_errors conn'
let result' = CUInt -> [TlsCertificateFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
touchManagedPtr conn
return result'
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetPeerCertificateErrorsMethodInfo
instance (signature ~ (m [Gio.Flags.TlsCertificateFlags]), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetPeerCertificateErrorsMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m [TlsCertificateFlags]
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m [TlsCertificateFlags]
dtlsConnectionGetPeerCertificateErrors
instance O.OverloadedMethodInfo DtlsConnectionGetPeerCertificateErrorsMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetPeerCertificateErrors",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetPeerCertificateErrors"
})
#endif
foreign import ccall "g_dtls_connection_get_protocol_version" g_dtls_connection_get_protocol_version ::
Ptr DtlsConnection ->
IO CUInt
dtlsConnectionGetProtocolVersion ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m Gio.Enums.TlsProtocolVersion
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_protocol_version conn'
let 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
touchManagedPtr conn
return result'
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetProtocolVersionMethodInfo
instance (signature ~ (m Gio.Enums.TlsProtocolVersion), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetProtocolVersionMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m TlsProtocolVersion
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m TlsProtocolVersion
dtlsConnectionGetProtocolVersion
instance O.OverloadedMethodInfo DtlsConnectionGetProtocolVersionMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetProtocolVersion",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetProtocolVersion"
})
#endif
foreign import ccall "g_dtls_connection_get_rehandshake_mode" g_dtls_connection_get_rehandshake_mode ::
Ptr 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."] #-}
dtlsConnectionGetRehandshakeMode ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m Gio.Enums.TlsRehandshakeMode
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_rehandshake_mode conn'
let 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
touchManagedPtr conn
return result'
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetRehandshakeModeMethodInfo
instance (signature ~ (m Gio.Enums.TlsRehandshakeMode), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetRehandshakeModeMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m TlsRehandshakeMode
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m TlsRehandshakeMode
dtlsConnectionGetRehandshakeMode
instance O.OverloadedMethodInfo DtlsConnectionGetRehandshakeModeMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetRehandshakeMode",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetRehandshakeMode"
})
#endif
foreign import ccall "g_dtls_connection_get_require_close_notify" g_dtls_connection_get_require_close_notify ::
Ptr DtlsConnection ->
IO CInt
dtlsConnectionGetRequireCloseNotify ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> m Bool
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result <- g_dtls_connection_get_require_close_notify conn'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr conn
return result'
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionGetRequireCloseNotifyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionGetRequireCloseNotifyMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m Bool
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> m Bool
dtlsConnectionGetRequireCloseNotify
instance O.OverloadedMethodInfo DtlsConnectionGetRequireCloseNotifyMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionGetRequireCloseNotify",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionGetRequireCloseNotify"
})
#endif
foreign import ccall "g_dtls_connection_handshake" g_dtls_connection_handshake ::
Ptr DtlsConnection ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
dtlsConnectionHandshake ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m ()
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
maybeCancellable <- case 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
FP.nullPtr
Just b
jCancellable -> do
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
return jCancellable'
onException (do
_ <- propagateGError $ g_dtls_connection_handshake conn' maybeCancellable
touchManagedPtr conn
whenJust cancellable touchManagedPtr
return ()
) (do
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 :: a -> signature
overloadedMethod = a -> signature
a -> Maybe b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Maybe b -> m ()
dtlsConnectionHandshake
instance O.OverloadedMethodInfo DtlsConnectionHandshakeMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionHandshake",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionHandshake"
})
#endif
foreign import ccall "g_dtls_connection_handshake_async" g_dtls_connection_handshake_async ::
Ptr DtlsConnection ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
dtlsConnectionHandshakeAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
a
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
maybeCancellable <- case 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
FP.nullPtr
Just b
jCancellable -> do
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
return jCancellable'
maybeCallback <- case 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 FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
poke ptrcallback jCallback'
return jCallback'
let userData = Ptr a
forall a. Ptr a
nullPtr
g_dtls_connection_handshake_async conn' ioPriority maybeCancellable maybeCallback userData
touchManagedPtr conn
whenJust cancellable touchManagedPtr
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 :: a -> signature
overloadedMethod = a -> signature
a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
dtlsConnectionHandshakeAsync
instance O.OverloadedMethodInfo DtlsConnectionHandshakeAsyncMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionHandshakeAsync",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionHandshakeAsync"
})
#endif
foreign import ccall "g_dtls_connection_handshake_finish" g_dtls_connection_handshake_finish ::
Ptr DtlsConnection ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
dtlsConnectionHandshakeFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result_' <- unsafeManagedPtrCastPtr result_
onException (do
_ <- propagateGError $ g_dtls_connection_handshake_finish conn' result_'
touchManagedPtr conn
touchManagedPtr result_
return ()
) (do
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 :: a -> signature
overloadedMethod = a -> signature
a -> b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsAsyncResult b) =>
a -> b -> m ()
dtlsConnectionHandshakeFinish
instance O.OverloadedMethodInfo DtlsConnectionHandshakeFinishMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionHandshakeFinish",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionHandshakeFinish"
})
#endif
foreign import ccall "g_dtls_connection_set_advertised_protocols" g_dtls_connection_set_advertised_protocols ::
Ptr DtlsConnection ->
Ptr CString ->
IO ()
dtlsConnectionSetAdvertisedProtocols ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> Maybe ([T.Text])
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
maybeProtocols <- case 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
FP.nullPtr
Just [Text]
jProtocols -> do
jProtocols' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jProtocols
return jProtocols'
g_dtls_connection_set_advertised_protocols conn' maybeProtocols
touchManagedPtr conn
mapZeroTerminatedCArray freeMem maybeProtocols
freeMem maybeProtocols
return ()
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionSetAdvertisedProtocolsMethodInfo
instance (signature ~ (Maybe ([T.Text]) -> m ()), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionSetAdvertisedProtocolsMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> Maybe [Text] -> m ()
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> Maybe [Text] -> m ()
dtlsConnectionSetAdvertisedProtocols
instance O.OverloadedMethodInfo DtlsConnectionSetAdvertisedProtocolsMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetAdvertisedProtocols",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetAdvertisedProtocols"
})
#endif
foreign import ccall "g_dtls_connection_set_certificate" g_dtls_connection_set_certificate ::
Ptr DtlsConnection ->
Ptr Gio.TlsCertificate.TlsCertificate ->
IO ()
dtlsConnectionSetCertificate ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.TlsCertificate.IsTlsCertificate b) =>
a
-> b
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
certificate' <- unsafeManagedPtrCastPtr certificate
g_dtls_connection_set_certificate conn' certificate'
touchManagedPtr conn
touchManagedPtr certificate
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 :: a -> signature
overloadedMethod = a -> signature
a -> b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a,
IsTlsCertificate b) =>
a -> b -> m ()
dtlsConnectionSetCertificate
instance O.OverloadedMethodInfo DtlsConnectionSetCertificateMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetCertificate",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetCertificate"
})
#endif
foreign import ccall "g_dtls_connection_set_database" g_dtls_connection_set_database ::
Ptr DtlsConnection ->
Ptr Gio.TlsDatabase.TlsDatabase ->
IO ()
dtlsConnectionSetDatabase ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.TlsDatabase.IsTlsDatabase b) =>
a
-> Maybe (b)
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
maybeDatabase <- case 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
FP.nullPtr
Just b
jDatabase -> do
jDatabase' <- b -> IO (Ptr TlsDatabase)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jDatabase
return jDatabase'
g_dtls_connection_set_database conn' maybeDatabase
touchManagedPtr conn
whenJust database touchManagedPtr
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 :: a -> signature
overloadedMethod = a -> signature
a -> Maybe b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsTlsDatabase b) =>
a -> Maybe b -> m ()
dtlsConnectionSetDatabase
instance O.OverloadedMethodInfo DtlsConnectionSetDatabaseMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetDatabase",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetDatabase"
})
#endif
foreign import ccall "g_dtls_connection_set_interaction" g_dtls_connection_set_interaction ::
Ptr DtlsConnection ->
Ptr Gio.TlsInteraction.TlsInteraction ->
IO ()
dtlsConnectionSetInteraction ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.TlsInteraction.IsTlsInteraction b) =>
a
-> Maybe (b)
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
maybeInteraction <- case 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
FP.nullPtr
Just b
jInteraction -> do
jInteraction' <- b -> IO (Ptr TlsInteraction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jInteraction
return jInteraction'
g_dtls_connection_set_interaction conn' maybeInteraction
touchManagedPtr conn
whenJust interaction touchManagedPtr
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 :: a -> signature
overloadedMethod = a -> signature
a -> Maybe b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a,
IsTlsInteraction b) =>
a -> Maybe b -> m ()
dtlsConnectionSetInteraction
instance O.OverloadedMethodInfo DtlsConnectionSetInteractionMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetInteraction",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetInteraction"
})
#endif
foreign import ccall "g_dtls_connection_set_rehandshake_mode" g_dtls_connection_set_rehandshake_mode ::
Ptr DtlsConnection ->
CUInt ->
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."] #-}
dtlsConnectionSetRehandshakeMode ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> Gio.Enums.TlsRehandshakeMode
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let 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
g_dtls_connection_set_rehandshake_mode conn' mode'
touchManagedPtr conn
return ()
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionSetRehandshakeModeMethodInfo
instance (signature ~ (Gio.Enums.TlsRehandshakeMode -> m ()), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionSetRehandshakeModeMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> TlsRehandshakeMode -> m ()
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> TlsRehandshakeMode -> m ()
dtlsConnectionSetRehandshakeMode
instance O.OverloadedMethodInfo DtlsConnectionSetRehandshakeModeMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetRehandshakeMode",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetRehandshakeMode"
})
#endif
foreign import ccall "g_dtls_connection_set_require_close_notify" g_dtls_connection_set_require_close_notify ::
Ptr DtlsConnection ->
CInt ->
IO ()
dtlsConnectionSetRequireCloseNotify ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a) =>
a
-> Bool
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let requireCloseNotify' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
requireCloseNotify
g_dtls_connection_set_require_close_notify conn' requireCloseNotify'
touchManagedPtr conn
return ()
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionSetRequireCloseNotifyMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDtlsConnection a) => O.OverloadedMethod DtlsConnectionSetRequireCloseNotifyMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> Bool -> m ()
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDtlsConnection a) =>
a -> Bool -> m ()
dtlsConnectionSetRequireCloseNotify
instance O.OverloadedMethodInfo DtlsConnectionSetRequireCloseNotifyMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionSetRequireCloseNotify",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionSetRequireCloseNotify"
})
#endif
foreign import ccall "g_dtls_connection_shutdown" g_dtls_connection_shutdown ::
Ptr DtlsConnection ->
CInt ->
CInt ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
dtlsConnectionShutdown ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
a
-> Bool
-> Bool
-> Maybe (b)
-> m ()
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let shutdownRead' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
shutdownRead
let shutdownWrite' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
shutdownWrite
maybeCancellable <- case 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
FP.nullPtr
Just b
jCancellable -> do
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
return jCancellable'
onException (do
_ <- propagateGError $ g_dtls_connection_shutdown conn' shutdownRead' shutdownWrite' maybeCancellable
touchManagedPtr conn
whenJust cancellable touchManagedPtr
return ()
) (do
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 :: a -> signature
overloadedMethod = a -> signature
a -> Bool -> Bool -> Maybe b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a -> Bool -> Bool -> Maybe b -> m ()
dtlsConnectionShutdown
instance O.OverloadedMethodInfo DtlsConnectionShutdownMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdown",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionShutdown"
})
#endif
foreign import ccall "g_dtls_connection_shutdown_async" g_dtls_connection_shutdown_async ::
Ptr DtlsConnection ->
CInt ->
CInt ->
Int32 ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
dtlsConnectionShutdownAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.Cancellable.IsCancellable b) =>
a
-> Bool
-> Bool
-> Int32
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> 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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
let shutdownRead' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
shutdownRead
let shutdownWrite' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
shutdownWrite
maybeCancellable <- case 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
FP.nullPtr
Just b
jCancellable -> do
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
return jCancellable'
maybeCallback <- case 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 FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
poke ptrcallback jCallback'
return jCallback'
let userData = Ptr a
forall a. Ptr a
nullPtr
g_dtls_connection_shutdown_async conn' shutdownRead' shutdownWrite' ioPriority maybeCancellable maybeCallback userData
touchManagedPtr conn
whenJust cancellable touchManagedPtr
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 :: a -> signature
overloadedMethod = a -> signature
a
-> Bool
-> Bool
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsCancellable b) =>
a
-> Bool
-> Bool
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
dtlsConnectionShutdownAsync
instance O.OverloadedMethodInfo DtlsConnectionShutdownAsyncMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdownAsync",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionShutdownAsync"
})
#endif
foreign import ccall "g_dtls_connection_shutdown_finish" g_dtls_connection_shutdown_finish ::
Ptr DtlsConnection ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
dtlsConnectionShutdownFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsDtlsConnection a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
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
conn' <- a -> IO (Ptr DtlsConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
result_' <- unsafeManagedPtrCastPtr result_
onException (do
_ <- propagateGError $ g_dtls_connection_shutdown_finish conn' result_'
touchManagedPtr conn
touchManagedPtr result_
return ()
) (do
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 :: a -> signature
overloadedMethod = a -> signature
a -> b -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDtlsConnection a, IsAsyncResult b) =>
a -> b -> m ()
dtlsConnectionShutdownFinish
instance O.OverloadedMethodInfo DtlsConnectionShutdownFinishMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection.dtlsConnectionShutdownFinish",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Interfaces-DtlsConnection.html#v:dtlsConnectionShutdownFinish"
})
#endif
type DtlsConnectionAcceptCertificateCallback =
Gio.TlsCertificate.TlsCertificate
-> [Gio.Flags.TlsCertificateFlags]
-> IO Bool
type C_DtlsConnectionAcceptCertificateCallback =
Ptr DtlsConnection ->
Ptr Gio.TlsCertificate.TlsCertificate ->
CUInt ->
Ptr () ->
IO CInt
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
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' = CUInt -> [TlsCertificateFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
errors
result <- B.ManagedPtr.withNewObject gi'selfPtr $ \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' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
result
return result'
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
wrapped'' <- C_DtlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_DtlsConnectionAcceptCertificateCallback)
mk_DtlsConnectionAcceptCertificateCallback C_DtlsConnectionAcceptCertificateCallback
wrapped'
connectSignalFunPtr obj "accept-certificate" wrapped'' SignalConnectBefore Nothing
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
wrapped'' <- C_DtlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_DtlsConnectionAcceptCertificateCallback)
mk_DtlsConnectionAcceptCertificateCallback C_DtlsConnectionAcceptCertificateCallback
wrapped'
connectSignalFunPtr obj "accept-certificate" wrapped'' SignalConnectAfter Nothing
#if defined(ENABLE_OVERLOADING)
data DtlsConnectionAcceptCertificateSignalInfo
instance SignalInfo DtlsConnectionAcceptCertificateSignalInfo where
type HaskellCallbackType DtlsConnectionAcceptCertificateSignalInfo = DtlsConnectionAcceptCertificateCallback
connectSignal :: forall o.
GObject o =>
o
-> (o
-> HaskellCallbackType DtlsConnectionAcceptCertificateSignalInfo)
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignal o
obj o -> HaskellCallbackType DtlsConnectionAcceptCertificateSignalInfo
cb SignalConnectMode
connectMode Maybe Text
detail = do
let cb' :: C_DtlsConnectionAcceptCertificateCallback
cb' = (o -> DtlsConnectionAcceptCertificateCallback)
-> C_DtlsConnectionAcceptCertificateCallback
forall a.
GObject a =>
(a -> DtlsConnectionAcceptCertificateCallback)
-> C_DtlsConnectionAcceptCertificateCallback
wrap_DtlsConnectionAcceptCertificateCallback o -> HaskellCallbackType DtlsConnectionAcceptCertificateSignalInfo
o -> DtlsConnectionAcceptCertificateCallback
cb
cb'' <- C_DtlsConnectionAcceptCertificateCallback
-> IO (FunPtr C_DtlsConnectionAcceptCertificateCallback)
mk_DtlsConnectionAcceptCertificateCallback C_DtlsConnectionAcceptCertificateCallback
cb'
connectSignalFunPtr obj "accept-certificate" cb'' connectMode detail
dbgSignalInfo :: Maybe ResolvedSymbolInfo
dbgSignalInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Interfaces.DtlsConnection::accept-certificate"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/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, DK.Type)])
#endif