{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.TlsServerConnection
(
TlsServerConnection(..) ,
IsTlsServerConnection ,
toTlsServerConnection ,
#if defined(ENABLE_OVERLOADING)
ResolveTlsServerConnectionMethod ,
#endif
tlsServerConnectionNew ,
#if defined(ENABLE_OVERLOADING)
TlsServerConnectionAuthenticationModePropertyInfo,
#endif
constructTlsServerConnectionAuthenticationMode,
getTlsServerConnectionAuthenticationMode,
setTlsServerConnectionAuthenticationMode,
#if defined(ENABLE_OVERLOADING)
tlsServerConnectionAuthenticationMode ,
#endif
) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsCertificate as Gio.TlsCertificate
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsConnection as Gio.TlsConnection
newtype TlsServerConnection = TlsServerConnection (SP.ManagedPtr TlsServerConnection)
deriving (TlsServerConnection -> TlsServerConnection -> Bool
(TlsServerConnection -> TlsServerConnection -> Bool)
-> (TlsServerConnection -> TlsServerConnection -> Bool)
-> Eq TlsServerConnection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsServerConnection -> TlsServerConnection -> Bool
$c/= :: TlsServerConnection -> TlsServerConnection -> Bool
== :: TlsServerConnection -> TlsServerConnection -> Bool
$c== :: TlsServerConnection -> TlsServerConnection -> Bool
Eq)
instance SP.ManagedPtrNewtype TlsServerConnection where
toManagedPtr :: TlsServerConnection -> ManagedPtr TlsServerConnection
toManagedPtr (TlsServerConnection ManagedPtr TlsServerConnection
p) = ManagedPtr TlsServerConnection
p
foreign import ccall "g_tls_server_connection_get_type"
c_g_tls_server_connection_get_type :: IO B.Types.GType
instance B.Types.TypedObject TlsServerConnection where
glibType :: IO GType
glibType = IO GType
c_g_tls_server_connection_get_type
instance B.Types.GObject TlsServerConnection
instance B.GValue.IsGValue TlsServerConnection where
toGValue :: TlsServerConnection -> IO GValue
toGValue TlsServerConnection
o = do
GType
gtype <- IO GType
c_g_tls_server_connection_get_type
TlsServerConnection
-> (Ptr TlsServerConnection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsServerConnection
o (GType
-> (GValue -> Ptr TlsServerConnection -> IO ())
-> Ptr TlsServerConnection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TlsServerConnection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO TlsServerConnection
fromGValue GValue
gv = do
Ptr TlsServerConnection
ptr <- GValue -> IO (Ptr TlsServerConnection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TlsServerConnection)
(ManagedPtr TlsServerConnection -> TlsServerConnection)
-> Ptr TlsServerConnection -> IO TlsServerConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TlsServerConnection -> TlsServerConnection
TlsServerConnection Ptr TlsServerConnection
ptr
class (SP.GObject o, O.IsDescendantOf TlsServerConnection o) => IsTlsServerConnection o
instance (SP.GObject o, O.IsDescendantOf TlsServerConnection o) => IsTlsServerConnection o
instance O.HasParentTypes TlsServerConnection
type instance O.ParentTypes TlsServerConnection = '[GObject.Object.Object, Gio.TlsConnection.TlsConnection, Gio.IOStream.IOStream]
toTlsServerConnection :: (MonadIO m, IsTlsServerConnection o) => o -> m TlsServerConnection
toTlsServerConnection :: o -> m TlsServerConnection
toTlsServerConnection = IO TlsServerConnection -> m TlsServerConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsServerConnection -> m TlsServerConnection)
-> (o -> IO TlsServerConnection) -> o -> m TlsServerConnection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TlsServerConnection -> TlsServerConnection)
-> o -> IO TlsServerConnection
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TlsServerConnection -> TlsServerConnection
TlsServerConnection
getTlsServerConnectionAuthenticationMode :: (MonadIO m, IsTlsServerConnection o) => o -> m Gio.Enums.TlsAuthenticationMode
getTlsServerConnectionAuthenticationMode :: o -> m TlsAuthenticationMode
getTlsServerConnectionAuthenticationMode o
obj = IO TlsAuthenticationMode -> m TlsAuthenticationMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsAuthenticationMode -> m TlsAuthenticationMode)
-> IO TlsAuthenticationMode -> m TlsAuthenticationMode
forall a b. (a -> b) -> a -> b
$ o -> String -> IO TlsAuthenticationMode
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"authentication-mode"
setTlsServerConnectionAuthenticationMode :: (MonadIO m, IsTlsServerConnection o) => o -> Gio.Enums.TlsAuthenticationMode -> m ()
setTlsServerConnectionAuthenticationMode :: o -> TlsAuthenticationMode -> m ()
setTlsServerConnectionAuthenticationMode o
obj TlsAuthenticationMode
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> TlsAuthenticationMode -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"authentication-mode" TlsAuthenticationMode
val
constructTlsServerConnectionAuthenticationMode :: (IsTlsServerConnection o, MIO.MonadIO m) => Gio.Enums.TlsAuthenticationMode -> m (GValueConstruct o)
constructTlsServerConnectionAuthenticationMode :: TlsAuthenticationMode -> m (GValueConstruct o)
constructTlsServerConnectionAuthenticationMode TlsAuthenticationMode
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> TlsAuthenticationMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"authentication-mode" TlsAuthenticationMode
val
#if defined(ENABLE_OVERLOADING)
data TlsServerConnectionAuthenticationModePropertyInfo
instance AttrInfo TlsServerConnectionAuthenticationModePropertyInfo where
type AttrAllowedOps TlsServerConnectionAuthenticationModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsServerConnectionAuthenticationModePropertyInfo = IsTlsServerConnection
type AttrSetTypeConstraint TlsServerConnectionAuthenticationModePropertyInfo = (~) Gio.Enums.TlsAuthenticationMode
type AttrTransferTypeConstraint TlsServerConnectionAuthenticationModePropertyInfo = (~) Gio.Enums.TlsAuthenticationMode
type AttrTransferType TlsServerConnectionAuthenticationModePropertyInfo = Gio.Enums.TlsAuthenticationMode
type AttrGetType TlsServerConnectionAuthenticationModePropertyInfo = Gio.Enums.TlsAuthenticationMode
type AttrLabel TlsServerConnectionAuthenticationModePropertyInfo = "authentication-mode"
type AttrOrigin TlsServerConnectionAuthenticationModePropertyInfo = TlsServerConnection
attrGet = getTlsServerConnectionAuthenticationMode
attrSet = setTlsServerConnectionAuthenticationMode
attrTransfer _ v = do
return v
attrConstruct = constructTlsServerConnectionAuthenticationMode
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsServerConnection
type instance O.AttributeList TlsServerConnection = TlsServerConnectionAttributeList
type TlsServerConnectionAttributeList = ('[ '("advertisedProtocols", Gio.TlsConnection.TlsConnectionAdvertisedProtocolsPropertyInfo), '("authenticationMode", TlsServerConnectionAuthenticationModePropertyInfo), '("baseIoStream", Gio.TlsConnection.TlsConnectionBaseIoStreamPropertyInfo), '("certificate", Gio.TlsConnection.TlsConnectionCertificatePropertyInfo), '("closed", Gio.IOStream.IOStreamClosedPropertyInfo), '("database", Gio.TlsConnection.TlsConnectionDatabasePropertyInfo), '("inputStream", Gio.IOStream.IOStreamInputStreamPropertyInfo), '("interaction", Gio.TlsConnection.TlsConnectionInteractionPropertyInfo), '("negotiatedProtocol", Gio.TlsConnection.TlsConnectionNegotiatedProtocolPropertyInfo), '("outputStream", Gio.IOStream.IOStreamOutputStreamPropertyInfo), '("peerCertificate", Gio.TlsConnection.TlsConnectionPeerCertificatePropertyInfo), '("peerCertificateErrors", Gio.TlsConnection.TlsConnectionPeerCertificateErrorsPropertyInfo), '("rehandshakeMode", Gio.TlsConnection.TlsConnectionRehandshakeModePropertyInfo), '("requireCloseNotify", Gio.TlsConnection.TlsConnectionRequireCloseNotifyPropertyInfo), '("useSystemCertdb", Gio.TlsConnection.TlsConnectionUseSystemCertdbPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
tlsServerConnectionAuthenticationMode :: AttrLabelProxy "authenticationMode"
tlsServerConnectionAuthenticationMode = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveTlsServerConnectionMethod (t :: Symbol) (o :: *) :: * where
ResolveTlsServerConnectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTlsServerConnectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTlsServerConnectionMethod "clearPending" o = Gio.IOStream.IOStreamClearPendingMethodInfo
ResolveTlsServerConnectionMethod "close" o = Gio.IOStream.IOStreamCloseMethodInfo
ResolveTlsServerConnectionMethod "closeAsync" o = Gio.IOStream.IOStreamCloseAsyncMethodInfo
ResolveTlsServerConnectionMethod "closeFinish" o = Gio.IOStream.IOStreamCloseFinishMethodInfo
ResolveTlsServerConnectionMethod "emitAcceptCertificate" o = Gio.TlsConnection.TlsConnectionEmitAcceptCertificateMethodInfo
ResolveTlsServerConnectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTlsServerConnectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTlsServerConnectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTlsServerConnectionMethod "handshake" o = Gio.TlsConnection.TlsConnectionHandshakeMethodInfo
ResolveTlsServerConnectionMethod "handshakeAsync" o = Gio.TlsConnection.TlsConnectionHandshakeAsyncMethodInfo
ResolveTlsServerConnectionMethod "handshakeFinish" o = Gio.TlsConnection.TlsConnectionHandshakeFinishMethodInfo
ResolveTlsServerConnectionMethod "hasPending" o = Gio.IOStream.IOStreamHasPendingMethodInfo
ResolveTlsServerConnectionMethod "isClosed" o = Gio.IOStream.IOStreamIsClosedMethodInfo
ResolveTlsServerConnectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTlsServerConnectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTlsServerConnectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTlsServerConnectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTlsServerConnectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTlsServerConnectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTlsServerConnectionMethod "spliceAsync" o = Gio.IOStream.IOStreamSpliceAsyncMethodInfo
ResolveTlsServerConnectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTlsServerConnectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTlsServerConnectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTlsServerConnectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTlsServerConnectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTlsServerConnectionMethod "getCertificate" o = Gio.TlsConnection.TlsConnectionGetCertificateMethodInfo
ResolveTlsServerConnectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTlsServerConnectionMethod "getDatabase" o = Gio.TlsConnection.TlsConnectionGetDatabaseMethodInfo
ResolveTlsServerConnectionMethod "getInputStream" o = Gio.IOStream.IOStreamGetInputStreamMethodInfo
ResolveTlsServerConnectionMethod "getInteraction" o = Gio.TlsConnection.TlsConnectionGetInteractionMethodInfo
ResolveTlsServerConnectionMethod "getNegotiatedProtocol" o = Gio.TlsConnection.TlsConnectionGetNegotiatedProtocolMethodInfo
ResolveTlsServerConnectionMethod "getOutputStream" o = Gio.IOStream.IOStreamGetOutputStreamMethodInfo
ResolveTlsServerConnectionMethod "getPeerCertificate" o = Gio.TlsConnection.TlsConnectionGetPeerCertificateMethodInfo
ResolveTlsServerConnectionMethod "getPeerCertificateErrors" o = Gio.TlsConnection.TlsConnectionGetPeerCertificateErrorsMethodInfo
ResolveTlsServerConnectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTlsServerConnectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTlsServerConnectionMethod "getRehandshakeMode" o = Gio.TlsConnection.TlsConnectionGetRehandshakeModeMethodInfo
ResolveTlsServerConnectionMethod "getRequireCloseNotify" o = Gio.TlsConnection.TlsConnectionGetRequireCloseNotifyMethodInfo
ResolveTlsServerConnectionMethod "getUseSystemCertdb" o = Gio.TlsConnection.TlsConnectionGetUseSystemCertdbMethodInfo
ResolveTlsServerConnectionMethod "setAdvertisedProtocols" o = Gio.TlsConnection.TlsConnectionSetAdvertisedProtocolsMethodInfo
ResolveTlsServerConnectionMethod "setCertificate" o = Gio.TlsConnection.TlsConnectionSetCertificateMethodInfo
ResolveTlsServerConnectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTlsServerConnectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTlsServerConnectionMethod "setDatabase" o = Gio.TlsConnection.TlsConnectionSetDatabaseMethodInfo
ResolveTlsServerConnectionMethod "setInteraction" o = Gio.TlsConnection.TlsConnectionSetInteractionMethodInfo
ResolveTlsServerConnectionMethod "setPending" o = Gio.IOStream.IOStreamSetPendingMethodInfo
ResolveTlsServerConnectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTlsServerConnectionMethod "setRehandshakeMode" o = Gio.TlsConnection.TlsConnectionSetRehandshakeModeMethodInfo
ResolveTlsServerConnectionMethod "setRequireCloseNotify" o = Gio.TlsConnection.TlsConnectionSetRequireCloseNotifyMethodInfo
ResolveTlsServerConnectionMethod "setUseSystemCertdb" o = Gio.TlsConnection.TlsConnectionSetUseSystemCertdbMethodInfo
ResolveTlsServerConnectionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTlsServerConnectionMethod t TlsServerConnection, O.MethodInfo info TlsServerConnection p) => OL.IsLabel t (TlsServerConnection -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "g_tls_server_connection_new" g_tls_server_connection_new ::
Ptr Gio.IOStream.IOStream ->
Ptr Gio.TlsCertificate.TlsCertificate ->
Ptr (Ptr GError) ->
IO (Ptr TlsServerConnection)
tlsServerConnectionNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.IOStream.IsIOStream a, Gio.TlsCertificate.IsTlsCertificate b) =>
a
-> Maybe (b)
-> m TlsServerConnection
tlsServerConnectionNew :: a -> Maybe b -> m TlsServerConnection
tlsServerConnectionNew a
baseIoStream Maybe b
certificate = IO TlsServerConnection -> m TlsServerConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsServerConnection -> m TlsServerConnection)
-> IO TlsServerConnection -> m TlsServerConnection
forall a b. (a -> b) -> a -> b
$ do
Ptr IOStream
baseIoStream' <- a -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
baseIoStream
Ptr TlsCertificate
maybeCertificate <- case Maybe b
certificate of
Maybe b
Nothing -> Ptr TlsCertificate -> IO (Ptr TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsCertificate
forall a. Ptr a
nullPtr
Just b
jCertificate -> do
Ptr TlsCertificate
jCertificate' <- b -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCertificate
Ptr TlsCertificate -> IO (Ptr TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsCertificate
jCertificate'
IO TlsServerConnection -> IO () -> IO TlsServerConnection
forall a b. IO a -> IO b -> IO a
onException (do
Ptr TlsServerConnection
result <- (Ptr (Ptr GError) -> IO (Ptr TlsServerConnection))
-> IO (Ptr TlsServerConnection)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr TlsServerConnection))
-> IO (Ptr TlsServerConnection))
-> (Ptr (Ptr GError) -> IO (Ptr TlsServerConnection))
-> IO (Ptr TlsServerConnection)
forall a b. (a -> b) -> a -> b
$ Ptr IOStream
-> Ptr TlsCertificate
-> Ptr (Ptr GError)
-> IO (Ptr TlsServerConnection)
g_tls_server_connection_new Ptr IOStream
baseIoStream' Ptr TlsCertificate
maybeCertificate
Text -> Ptr TlsServerConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsServerConnectionNew" Ptr TlsServerConnection
result
TlsServerConnection
result' <- ((ManagedPtr TlsServerConnection -> TlsServerConnection)
-> Ptr TlsServerConnection -> IO TlsServerConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsServerConnection -> TlsServerConnection
TlsServerConnection) Ptr TlsServerConnection
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
baseIoStream
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
certificate b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
TlsServerConnection -> IO TlsServerConnection
forall (m :: * -> *) a. Monad m => a -> m a
return TlsServerConnection
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TlsServerConnection = TlsServerConnectionSignalList
type TlsServerConnectionSignalList = ('[ '("acceptCertificate", Gio.TlsConnection.TlsConnectionAcceptCertificateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif