{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection' is the client-side subclass of
-- t'GI.Gio.Objects.TlsConnection.TlsConnection', representing a client-side TLS connection.
-- 
-- /Since: 2.28/

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

module GI.Gio.Interfaces.TlsClientConnection
    ( 

-- * Exported types
    TlsClientConnection(..)                 ,
    IsTlsClientConnection                   ,
    toTlsClientConnection                   ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveTlsClientConnectionMethod        ,
#endif


-- ** copySessionState #method:copySessionState#

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionCopySessionStateMethodInfo,
#endif
    tlsClientConnectionCopySessionState     ,


-- ** getAcceptedCas #method:getAcceptedCas#

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionGetAcceptedCasMethodInfo,
#endif
    tlsClientConnectionGetAcceptedCas       ,


-- ** getServerIdentity #method:getServerIdentity#

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionGetServerIdentityMethodInfo,
#endif
    tlsClientConnectionGetServerIdentity    ,


-- ** getUseSsl3 #method:getUseSsl3#

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionGetUseSsl3MethodInfo ,
#endif
    tlsClientConnectionGetUseSsl3           ,


-- ** getValidationFlags #method:getValidationFlags#

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionGetValidationFlagsMethodInfo,
#endif
    tlsClientConnectionGetValidationFlags   ,


-- ** new #method:new#

    tlsClientConnectionNew                  ,


-- ** setServerIdentity #method:setServerIdentity#

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionSetServerIdentityMethodInfo,
#endif
    tlsClientConnectionSetServerIdentity    ,


-- ** setUseSsl3 #method:setUseSsl3#

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionSetUseSsl3MethodInfo ,
#endif
    tlsClientConnectionSetUseSsl3           ,


-- ** setValidationFlags #method:setValidationFlags#

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionSetValidationFlagsMethodInfo,
#endif
    tlsClientConnectionSetValidationFlags   ,




 -- * Properties
-- ** acceptedCas #attr:acceptedCas#
-- | A list of the distinguished names of the Certificate Authorities
-- that the server will accept client certificates signed by. If the
-- server requests a client certificate during the handshake, then
-- this property will be set after the handshake completes.
-- 
-- Each item in the list is a t'GI.GLib.Structs.ByteArray.ByteArray' which contains the complete
-- subject DN of the certificate authority.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionAcceptedCasPropertyInfo,
#endif
    getTlsClientConnectionAcceptedCas       ,
#if defined(ENABLE_OVERLOADING)
    tlsClientConnectionAcceptedCas          ,
#endif


-- ** serverIdentity #attr:serverIdentity#
-- | A t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' describing the identity of the server that
-- is expected on the other end of the connection.
-- 
-- If the 'GI.Gio.Flags.TlsCertificateFlagsBadIdentity' flag is set in
-- t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection':@/validation-flags/@, this object will be used
-- to determine the expected identify of the remote end of the
-- connection; if t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection':@/server-identity/@ is not set,
-- or does not match the identity presented by the server, then the
-- 'GI.Gio.Flags.TlsCertificateFlagsBadIdentity' validation will fail.
-- 
-- In addition to its use in verifying the server certificate,
-- this is also used to give a hint to the server about what
-- certificate we expect, which is useful for servers that serve
-- virtual hosts.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionServerIdentityPropertyInfo,
#endif
    constructTlsClientConnectionServerIdentity,
    getTlsClientConnectionServerIdentity    ,
    setTlsClientConnectionServerIdentity    ,
#if defined(ENABLE_OVERLOADING)
    tlsClientConnectionServerIdentity       ,
#endif


-- ** useSsl3 #attr:useSsl3#
-- | SSL 3.0 is no longer supported. See
-- 'GI.Gio.Interfaces.TlsClientConnection.tlsClientConnectionSetUseSsl3' for details.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionUseSsl3PropertyInfo  ,
#endif
    constructTlsClientConnectionUseSsl3     ,
    getTlsClientConnectionUseSsl3           ,
    setTlsClientConnectionUseSsl3           ,
#if defined(ENABLE_OVERLOADING)
    tlsClientConnectionUseSsl3              ,
#endif


-- ** validationFlags #attr:validationFlags#
-- | What steps to perform when validating a certificate received from
-- a server. Server certificates that fail to validate in all of the
-- ways indicated here will be rejected unless the application
-- overrides the default via [acceptCertificate]("GI.Gio.Objects.TlsConnection#g:signal:acceptCertificate").
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsClientConnectionValidationFlagsPropertyInfo,
#endif
    constructTlsClientConnectionValidationFlags,
    getTlsClientConnectionValidationFlags   ,
    setTlsClientConnectionValidationFlags   ,
#if defined(ENABLE_OVERLOADING)
    tlsClientConnectionValidationFlags      ,
#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.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.TlsConnection as Gio.TlsConnection

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

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

foreign import ccall "g_tls_client_connection_get_type"
    c_g_tls_client_connection_get_type :: IO B.Types.GType

instance B.Types.TypedObject TlsClientConnection where
    glibType :: IO GType
glibType = IO GType
c_g_tls_client_connection_get_type

instance B.Types.GObject TlsClientConnection

-- | Convert 'TlsClientConnection' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue TlsClientConnection where
    toGValue :: TlsClientConnection -> IO GValue
toGValue TlsClientConnection
o = do
        GType
gtype <- IO GType
c_g_tls_client_connection_get_type
        TlsClientConnection
-> (Ptr TlsClientConnection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsClientConnection
o (GType
-> (GValue -> Ptr TlsClientConnection -> IO ())
-> Ptr TlsClientConnection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TlsClientConnection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO TlsClientConnection
fromGValue GValue
gv = do
        Ptr TlsClientConnection
ptr <- GValue -> IO (Ptr TlsClientConnection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TlsClientConnection)
        (ManagedPtr TlsClientConnection -> TlsClientConnection)
-> Ptr TlsClientConnection -> IO TlsClientConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TlsClientConnection -> TlsClientConnection
TlsClientConnection Ptr TlsClientConnection
ptr
        
    

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

instance O.HasParentTypes TlsClientConnection
type instance O.ParentTypes TlsClientConnection = '[GObject.Object.Object, Gio.TlsConnection.TlsConnection, Gio.IOStream.IOStream]

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

-- VVV Prop "accepted-cas"
   -- Type: TGList (TBasicType TPtr)
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accepted-cas@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsClientConnection #acceptedCas
-- @
getTlsClientConnectionAcceptedCas :: (MonadIO m, IsTlsClientConnection o) => o -> m ([Ptr ()])
getTlsClientConnectionAcceptedCas :: o -> m [Ptr ()]
getTlsClientConnectionAcceptedCas o
obj = IO [Ptr ()] -> m [Ptr ()]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Ptr ()] -> m [Ptr ()]) -> IO [Ptr ()] -> m [Ptr ()]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [Ptr ()]
forall a b. GObject a => a -> String -> IO [Ptr b]
B.Properties.getObjectPropertyPtrGList o
obj String
"accepted-cas"

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionAcceptedCasPropertyInfo
instance AttrInfo TlsClientConnectionAcceptedCasPropertyInfo where
    type AttrAllowedOps TlsClientConnectionAcceptedCasPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint TlsClientConnectionAcceptedCasPropertyInfo = IsTlsClientConnection
    type AttrSetTypeConstraint TlsClientConnectionAcceptedCasPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsClientConnectionAcceptedCasPropertyInfo = (~) ()
    type AttrTransferType TlsClientConnectionAcceptedCasPropertyInfo = ()
    type AttrGetType TlsClientConnectionAcceptedCasPropertyInfo = ([Ptr ()])
    type AttrLabel TlsClientConnectionAcceptedCasPropertyInfo = "accepted-cas"
    type AttrOrigin TlsClientConnectionAcceptedCasPropertyInfo = TlsClientConnection
    attrGet = getTlsClientConnectionAcceptedCas
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "server-identity"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketConnectable"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@server-identity@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsClientConnection #serverIdentity
-- @
getTlsClientConnectionServerIdentity :: (MonadIO m, IsTlsClientConnection o) => o -> m Gio.SocketConnectable.SocketConnectable
getTlsClientConnectionServerIdentity :: o -> m SocketConnectable
getTlsClientConnectionServerIdentity o
obj = IO SocketConnectable -> m SocketConnectable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketConnectable -> m SocketConnectable)
-> IO SocketConnectable -> m SocketConnectable
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe SocketConnectable) -> IO SocketConnectable
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTlsClientConnectionServerIdentity" (IO (Maybe SocketConnectable) -> IO SocketConnectable)
-> IO (Maybe SocketConnectable) -> IO SocketConnectable
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr SocketConnectable -> SocketConnectable)
-> IO (Maybe SocketConnectable)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"server-identity" ManagedPtr SocketConnectable -> SocketConnectable
Gio.SocketConnectable.SocketConnectable

-- | Set the value of the “@server-identity@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsClientConnection [ #serverIdentity 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsClientConnectionServerIdentity :: (MonadIO m, IsTlsClientConnection o, Gio.SocketConnectable.IsSocketConnectable a) => o -> a -> m ()
setTlsClientConnectionServerIdentity :: o -> a -> m ()
setTlsClientConnectionServerIdentity o
obj a
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 -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"server-identity" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@server-identity@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsClientConnectionServerIdentity :: (IsTlsClientConnection o, MIO.MonadIO m, Gio.SocketConnectable.IsSocketConnectable a) => a -> m (GValueConstruct o)
constructTlsClientConnectionServerIdentity :: a -> m (GValueConstruct o)
constructTlsClientConnectionServerIdentity a
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 -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"server-identity" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionServerIdentityPropertyInfo
instance AttrInfo TlsClientConnectionServerIdentityPropertyInfo where
    type AttrAllowedOps TlsClientConnectionServerIdentityPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TlsClientConnectionServerIdentityPropertyInfo = IsTlsClientConnection
    type AttrSetTypeConstraint TlsClientConnectionServerIdentityPropertyInfo = Gio.SocketConnectable.IsSocketConnectable
    type AttrTransferTypeConstraint TlsClientConnectionServerIdentityPropertyInfo = Gio.SocketConnectable.IsSocketConnectable
    type AttrTransferType TlsClientConnectionServerIdentityPropertyInfo = Gio.SocketConnectable.SocketConnectable
    type AttrGetType TlsClientConnectionServerIdentityPropertyInfo = Gio.SocketConnectable.SocketConnectable
    type AttrLabel TlsClientConnectionServerIdentityPropertyInfo = "server-identity"
    type AttrOrigin TlsClientConnectionServerIdentityPropertyInfo = TlsClientConnection
    attrGet = getTlsClientConnectionServerIdentity
    attrSet = setTlsClientConnectionServerIdentity
    attrTransfer _ v = do
        unsafeCastTo Gio.SocketConnectable.SocketConnectable v
    attrConstruct = constructTlsClientConnectionServerIdentity
    attrClear = undefined
#endif

-- VVV Prop "use-ssl3"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@use-ssl3@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsClientConnection #useSsl3
-- @
getTlsClientConnectionUseSsl3 :: (MonadIO m, IsTlsClientConnection o) => o -> m Bool
getTlsClientConnectionUseSsl3 :: o -> m Bool
getTlsClientConnectionUseSsl3 o
obj = IO Bool -> m Bool
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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"use-ssl3"

-- | Set the value of the “@use-ssl3@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsClientConnection [ #useSsl3 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsClientConnectionUseSsl3 :: (MonadIO m, IsTlsClientConnection o) => o -> Bool -> m ()
setTlsClientConnectionUseSsl3 :: o -> Bool -> m ()
setTlsClientConnectionUseSsl3 o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-ssl3" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@use-ssl3@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsClientConnectionUseSsl3 :: (IsTlsClientConnection o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTlsClientConnectionUseSsl3 :: Bool -> m (GValueConstruct o)
constructTlsClientConnectionUseSsl3 Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-ssl3" Bool
val

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionUseSsl3PropertyInfo
instance AttrInfo TlsClientConnectionUseSsl3PropertyInfo where
    type AttrAllowedOps TlsClientConnectionUseSsl3PropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TlsClientConnectionUseSsl3PropertyInfo = IsTlsClientConnection
    type AttrSetTypeConstraint TlsClientConnectionUseSsl3PropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TlsClientConnectionUseSsl3PropertyInfo = (~) Bool
    type AttrTransferType TlsClientConnectionUseSsl3PropertyInfo = Bool
    type AttrGetType TlsClientConnectionUseSsl3PropertyInfo = Bool
    type AttrLabel TlsClientConnectionUseSsl3PropertyInfo = "use-ssl3"
    type AttrOrigin TlsClientConnectionUseSsl3PropertyInfo = TlsClientConnection
    attrGet = getTlsClientConnectionUseSsl3
    attrSet = setTlsClientConnectionUseSsl3
    attrTransfer _ v = do
        return v
    attrConstruct = constructTlsClientConnectionUseSsl3
    attrClear = undefined
#endif

-- VVV Prop "validation-flags"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsCertificateFlags"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@validation-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsClientConnection #validationFlags
-- @
getTlsClientConnectionValidationFlags :: (MonadIO m, IsTlsClientConnection o) => o -> m [Gio.Flags.TlsCertificateFlags]
getTlsClientConnectionValidationFlags :: o -> m [TlsCertificateFlags]
getTlsClientConnectionValidationFlags o
obj = IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
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
$ o -> String -> IO [TlsCertificateFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"validation-flags"

-- | Set the value of the “@validation-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsClientConnection [ #validationFlags 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsClientConnectionValidationFlags :: (MonadIO m, IsTlsClientConnection o) => o -> [Gio.Flags.TlsCertificateFlags] -> m ()
setTlsClientConnectionValidationFlags :: o -> [TlsCertificateFlags] -> m ()
setTlsClientConnectionValidationFlags o
obj [TlsCertificateFlags]
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 -> [TlsCertificateFlags] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"validation-flags" [TlsCertificateFlags]
val

-- | Construct a `GValueConstruct` with valid value for the “@validation-flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsClientConnectionValidationFlags :: (IsTlsClientConnection o, MIO.MonadIO m) => [Gio.Flags.TlsCertificateFlags] -> m (GValueConstruct o)
constructTlsClientConnectionValidationFlags :: [TlsCertificateFlags] -> m (GValueConstruct o)
constructTlsClientConnectionValidationFlags [TlsCertificateFlags]
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 -> [TlsCertificateFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"validation-flags" [TlsCertificateFlags]
val

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionValidationFlagsPropertyInfo
instance AttrInfo TlsClientConnectionValidationFlagsPropertyInfo where
    type AttrAllowedOps TlsClientConnectionValidationFlagsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TlsClientConnectionValidationFlagsPropertyInfo = IsTlsClientConnection
    type AttrSetTypeConstraint TlsClientConnectionValidationFlagsPropertyInfo = (~) [Gio.Flags.TlsCertificateFlags]
    type AttrTransferTypeConstraint TlsClientConnectionValidationFlagsPropertyInfo = (~) [Gio.Flags.TlsCertificateFlags]
    type AttrTransferType TlsClientConnectionValidationFlagsPropertyInfo = [Gio.Flags.TlsCertificateFlags]
    type AttrGetType TlsClientConnectionValidationFlagsPropertyInfo = [Gio.Flags.TlsCertificateFlags]
    type AttrLabel TlsClientConnectionValidationFlagsPropertyInfo = "validation-flags"
    type AttrOrigin TlsClientConnectionValidationFlagsPropertyInfo = TlsClientConnection
    attrGet = getTlsClientConnectionValidationFlags
    attrSet = setTlsClientConnectionValidationFlags
    attrTransfer _ v = do
        return v
    attrConstruct = constructTlsClientConnectionValidationFlags
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsClientConnection
type instance O.AttributeList TlsClientConnection = TlsClientConnectionAttributeList
type TlsClientConnectionAttributeList = ('[ '("acceptedCas", TlsClientConnectionAcceptedCasPropertyInfo), '("advertisedProtocols", Gio.TlsConnection.TlsConnectionAdvertisedProtocolsPropertyInfo), '("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), '("serverIdentity", TlsClientConnectionServerIdentityPropertyInfo), '("useSsl3", TlsClientConnectionUseSsl3PropertyInfo), '("useSystemCertdb", Gio.TlsConnection.TlsConnectionUseSystemCertdbPropertyInfo), '("validationFlags", TlsClientConnectionValidationFlagsPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
tlsClientConnectionAcceptedCas :: AttrLabelProxy "acceptedCas"
tlsClientConnectionAcceptedCas = AttrLabelProxy

tlsClientConnectionServerIdentity :: AttrLabelProxy "serverIdentity"
tlsClientConnectionServerIdentity = AttrLabelProxy

tlsClientConnectionUseSsl3 :: AttrLabelProxy "useSsl3"
tlsClientConnectionUseSsl3 = AttrLabelProxy

tlsClientConnectionValidationFlags :: AttrLabelProxy "validationFlags"
tlsClientConnectionValidationFlags = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTlsClientConnectionMethod (t :: Symbol) (o :: *) :: * where
    ResolveTlsClientConnectionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTlsClientConnectionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTlsClientConnectionMethod "clearPending" o = Gio.IOStream.IOStreamClearPendingMethodInfo
    ResolveTlsClientConnectionMethod "close" o = Gio.IOStream.IOStreamCloseMethodInfo
    ResolveTlsClientConnectionMethod "closeAsync" o = Gio.IOStream.IOStreamCloseAsyncMethodInfo
    ResolveTlsClientConnectionMethod "closeFinish" o = Gio.IOStream.IOStreamCloseFinishMethodInfo
    ResolveTlsClientConnectionMethod "copySessionState" o = TlsClientConnectionCopySessionStateMethodInfo
    ResolveTlsClientConnectionMethod "emitAcceptCertificate" o = Gio.TlsConnection.TlsConnectionEmitAcceptCertificateMethodInfo
    ResolveTlsClientConnectionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTlsClientConnectionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTlsClientConnectionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTlsClientConnectionMethod "handshake" o = Gio.TlsConnection.TlsConnectionHandshakeMethodInfo
    ResolveTlsClientConnectionMethod "handshakeAsync" o = Gio.TlsConnection.TlsConnectionHandshakeAsyncMethodInfo
    ResolveTlsClientConnectionMethod "handshakeFinish" o = Gio.TlsConnection.TlsConnectionHandshakeFinishMethodInfo
    ResolveTlsClientConnectionMethod "hasPending" o = Gio.IOStream.IOStreamHasPendingMethodInfo
    ResolveTlsClientConnectionMethod "isClosed" o = Gio.IOStream.IOStreamIsClosedMethodInfo
    ResolveTlsClientConnectionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTlsClientConnectionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTlsClientConnectionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTlsClientConnectionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTlsClientConnectionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTlsClientConnectionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTlsClientConnectionMethod "spliceAsync" o = Gio.IOStream.IOStreamSpliceAsyncMethodInfo
    ResolveTlsClientConnectionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTlsClientConnectionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTlsClientConnectionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTlsClientConnectionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTlsClientConnectionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTlsClientConnectionMethod "getAcceptedCas" o = TlsClientConnectionGetAcceptedCasMethodInfo
    ResolveTlsClientConnectionMethod "getCertificate" o = Gio.TlsConnection.TlsConnectionGetCertificateMethodInfo
    ResolveTlsClientConnectionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTlsClientConnectionMethod "getDatabase" o = Gio.TlsConnection.TlsConnectionGetDatabaseMethodInfo
    ResolveTlsClientConnectionMethod "getInputStream" o = Gio.IOStream.IOStreamGetInputStreamMethodInfo
    ResolveTlsClientConnectionMethod "getInteraction" o = Gio.TlsConnection.TlsConnectionGetInteractionMethodInfo
    ResolveTlsClientConnectionMethod "getNegotiatedProtocol" o = Gio.TlsConnection.TlsConnectionGetNegotiatedProtocolMethodInfo
    ResolveTlsClientConnectionMethod "getOutputStream" o = Gio.IOStream.IOStreamGetOutputStreamMethodInfo
    ResolveTlsClientConnectionMethod "getPeerCertificate" o = Gio.TlsConnection.TlsConnectionGetPeerCertificateMethodInfo
    ResolveTlsClientConnectionMethod "getPeerCertificateErrors" o = Gio.TlsConnection.TlsConnectionGetPeerCertificateErrorsMethodInfo
    ResolveTlsClientConnectionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTlsClientConnectionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTlsClientConnectionMethod "getRehandshakeMode" o = Gio.TlsConnection.TlsConnectionGetRehandshakeModeMethodInfo
    ResolveTlsClientConnectionMethod "getRequireCloseNotify" o = Gio.TlsConnection.TlsConnectionGetRequireCloseNotifyMethodInfo
    ResolveTlsClientConnectionMethod "getServerIdentity" o = TlsClientConnectionGetServerIdentityMethodInfo
    ResolveTlsClientConnectionMethod "getUseSsl3" o = TlsClientConnectionGetUseSsl3MethodInfo
    ResolveTlsClientConnectionMethod "getUseSystemCertdb" o = Gio.TlsConnection.TlsConnectionGetUseSystemCertdbMethodInfo
    ResolveTlsClientConnectionMethod "getValidationFlags" o = TlsClientConnectionGetValidationFlagsMethodInfo
    ResolveTlsClientConnectionMethod "setAdvertisedProtocols" o = Gio.TlsConnection.TlsConnectionSetAdvertisedProtocolsMethodInfo
    ResolveTlsClientConnectionMethod "setCertificate" o = Gio.TlsConnection.TlsConnectionSetCertificateMethodInfo
    ResolveTlsClientConnectionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTlsClientConnectionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTlsClientConnectionMethod "setDatabase" o = Gio.TlsConnection.TlsConnectionSetDatabaseMethodInfo
    ResolveTlsClientConnectionMethod "setInteraction" o = Gio.TlsConnection.TlsConnectionSetInteractionMethodInfo
    ResolveTlsClientConnectionMethod "setPending" o = Gio.IOStream.IOStreamSetPendingMethodInfo
    ResolveTlsClientConnectionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTlsClientConnectionMethod "setRehandshakeMode" o = Gio.TlsConnection.TlsConnectionSetRehandshakeModeMethodInfo
    ResolveTlsClientConnectionMethod "setRequireCloseNotify" o = Gio.TlsConnection.TlsConnectionSetRequireCloseNotifyMethodInfo
    ResolveTlsClientConnectionMethod "setServerIdentity" o = TlsClientConnectionSetServerIdentityMethodInfo
    ResolveTlsClientConnectionMethod "setUseSsl3" o = TlsClientConnectionSetUseSsl3MethodInfo
    ResolveTlsClientConnectionMethod "setUseSystemCertdb" o = Gio.TlsConnection.TlsConnectionSetUseSystemCertdbMethodInfo
    ResolveTlsClientConnectionMethod "setValidationFlags" o = TlsClientConnectionSetValidationFlagsMethodInfo
    ResolveTlsClientConnectionMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTlsClientConnectionMethod t TlsClientConnection, O.MethodInfo info TlsClientConnection p) => OL.IsLabel t (TlsClientConnection -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- method TlsClientConnection::copy_session_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_client_connection_copy_session_state" g_tls_client_connection_copy_session_state :: 
    Ptr TlsClientConnection ->              -- conn : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    Ptr TlsClientConnection ->              -- source : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    IO ()

-- | Possibly copies session state from one connection to another, for use
-- in TLS session resumption. This is not normally needed, but may be
-- used when the same session needs to be used between different
-- endpoints, as is required by some protocols, such as FTP over TLS.
-- /@source@/ should have already completed a handshake and, since TLS 1.3,
-- it should have been used to read data at least once. /@conn@/ should not
-- have completed a handshake.
-- 
-- It is not possible to know whether a call to this function will
-- actually do anything. Because session resumption is normally used
-- only for performance benefit, the TLS backend might not implement
-- this function. Even if implemented, it may not actually succeed in
-- allowing /@conn@/ to resume /@source@/\'s TLS session, because the server
-- may not have sent a session resumption token to /@source@/, or it may
-- refuse to accept the token from /@conn@/. There is no way to know
-- whether a call to this function is actually successful.
-- 
-- Using this function is not required to benefit from session
-- resumption. If the TLS backend supports session resumption, the
-- session will be resumed automatically if it is possible to do so
-- without weakening the privacy guarantees normally provided by TLS,
-- without need to call this function. For example, with TLS 1.3,
-- a session ticket will be automatically copied from any
-- t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection' that has previously received session tickets
-- from the server, provided a ticket is available that has not
-- previously been used for session resumption, since session ticket
-- reuse would be a privacy weakness. Using this function causes the
-- ticket to be copied without regard for privacy considerations.
-- 
-- /Since: 2.46/
tlsClientConnectionCopySessionState ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a, IsTlsClientConnection b) =>
    a
    -- ^ /@conn@/: a t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> b
    -- ^ /@source@/: a t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> m ()
tlsClientConnectionCopySessionState :: a -> b -> m ()
tlsClientConnectionCopySessionState a
conn b
source = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    Ptr TlsClientConnection
source' <- b -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
source
    Ptr TlsClientConnection -> Ptr TlsClientConnection -> IO ()
g_tls_client_connection_copy_session_state Ptr TlsClientConnection
conn' Ptr TlsClientConnection
source'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
source
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionCopySessionStateMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTlsClientConnection a, IsTlsClientConnection b) => O.MethodInfo TlsClientConnectionCopySessionStateMethodInfo a signature where
    overloadedMethod = tlsClientConnectionCopySessionState

#endif

-- method TlsClientConnection::get_accepted_cas
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGList TByteArray)
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_client_connection_get_accepted_cas" g_tls_client_connection_get_accepted_cas :: 
    Ptr TlsClientConnection ->              -- conn : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    IO (Ptr (GList (Ptr GByteArray)))

-- | Gets the list of distinguished names of the Certificate Authorities
-- that the server will accept certificates from. This will be set
-- during the TLS handshake if the server requests a certificate.
-- Otherwise, it will be 'P.Nothing'.
-- 
-- Each item in the list is a t'GI.GLib.Structs.ByteArray.ByteArray' which contains the complete
-- subject DN of the certificate authority.
-- 
-- /Since: 2.28/
tlsClientConnectionGetAcceptedCas ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
    a
    -- ^ /@conn@/: the t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> m [ByteString]
    -- ^ __Returns:__ the list of
    -- CA DNs. You should unref each element with 'GI.GLib.Functions.byteArrayUnref' and then
    -- the free the list with @/g_list_free()/@.
tlsClientConnectionGetAcceptedCas :: a -> m [ByteString]
tlsClientConnectionGetAcceptedCas a
conn = IO [ByteString] -> m [ByteString]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ByteString] -> m [ByteString])
-> IO [ByteString] -> m [ByteString]
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    Ptr (GList (Ptr GByteArray))
result <- Ptr TlsClientConnection -> IO (Ptr (GList (Ptr GByteArray)))
g_tls_client_connection_get_accepted_cas Ptr TlsClientConnection
conn'
    [Ptr GByteArray]
result' <- Ptr (GList (Ptr GByteArray)) -> IO [Ptr GByteArray]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr GByteArray))
result
    [ByteString]
result'' <- (Ptr GByteArray -> IO ByteString)
-> [Ptr GByteArray] -> IO [ByteString]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Ptr GByteArray -> IO ByteString
unpackGByteArray [Ptr GByteArray]
result'
    (Ptr GByteArray -> IO ()) -> Ptr (GList (Ptr GByteArray)) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (GList (Ptr a)) -> IO ()
mapGList Ptr GByteArray -> IO ()
unrefGByteArray Ptr (GList (Ptr GByteArray))
result
    Ptr (GList (Ptr GByteArray)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr GByteArray))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    [ByteString] -> IO [ByteString]
forall (m :: * -> *) a. Monad m => a -> m a
return [ByteString]
result''

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionGetAcceptedCasMethodInfo
instance (signature ~ (m [ByteString]), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionGetAcceptedCasMethodInfo a signature where
    overloadedMethod = tlsClientConnectionGetAcceptedCas

#endif

-- method TlsClientConnection::get_server_identity
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SocketConnectable" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_client_connection_get_server_identity" g_tls_client_connection_get_server_identity :: 
    Ptr TlsClientConnection ->              -- conn : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    IO (Ptr Gio.SocketConnectable.SocketConnectable)

-- | Gets /@conn@/\'s expected server identity
-- 
-- /Since: 2.28/
tlsClientConnectionGetServerIdentity ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
    a
    -- ^ /@conn@/: the t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> m Gio.SocketConnectable.SocketConnectable
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' describing the
    -- expected server identity, or 'P.Nothing' if the expected identity is not
    -- known.
tlsClientConnectionGetServerIdentity :: a -> m SocketConnectable
tlsClientConnectionGetServerIdentity a
conn = IO SocketConnectable -> m SocketConnectable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SocketConnectable -> m SocketConnectable)
-> IO SocketConnectable -> m SocketConnectable
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    Ptr SocketConnectable
result <- Ptr TlsClientConnection -> IO (Ptr SocketConnectable)
g_tls_client_connection_get_server_identity Ptr TlsClientConnection
conn'
    Text -> Ptr SocketConnectable -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsClientConnectionGetServerIdentity" Ptr SocketConnectable
result
    SocketConnectable
result' <- ((ManagedPtr SocketConnectable -> SocketConnectable)
-> Ptr SocketConnectable -> IO SocketConnectable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr SocketConnectable -> SocketConnectable
Gio.SocketConnectable.SocketConnectable) Ptr SocketConnectable
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    SocketConnectable -> IO SocketConnectable
forall (m :: * -> *) a. Monad m => a -> m a
return SocketConnectable
result'

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionGetServerIdentityMethodInfo
instance (signature ~ (m Gio.SocketConnectable.SocketConnectable), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionGetServerIdentityMethodInfo a signature where
    overloadedMethod = tlsClientConnectionGetServerIdentity

#endif

-- method TlsClientConnection::get_use_ssl3
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_client_connection_get_use_ssl3" g_tls_client_connection_get_use_ssl3 :: 
    Ptr TlsClientConnection ->              -- conn : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    IO CInt

{-# DEPRECATED tlsClientConnectionGetUseSsl3 ["(Since version 2.56)","SSL 3.0 is insecure."] #-}
-- | SSL 3.0 is no longer supported. See
-- 'GI.Gio.Interfaces.TlsClientConnection.tlsClientConnectionSetUseSsl3' for details.
-- 
-- /Since: 2.28/
tlsClientConnectionGetUseSsl3 ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
    a
    -- ^ /@conn@/: the t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> m Bool
    -- ^ __Returns:__ 'P.False'
tlsClientConnectionGetUseSsl3 :: a -> m Bool
tlsClientConnectionGetUseSsl3 a
conn = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    CInt
result <- Ptr TlsClientConnection -> IO CInt
g_tls_client_connection_get_use_ssl3 Ptr TlsClientConnection
conn'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionGetUseSsl3MethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionGetUseSsl3MethodInfo a signature where
    overloadedMethod = tlsClientConnectionGetUseSsl3

#endif

-- method TlsClientConnection::get_validation_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "TlsCertificateFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_client_connection_get_validation_flags" g_tls_client_connection_get_validation_flags :: 
    Ptr TlsClientConnection ->              -- conn : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    IO CUInt

-- | Gets /@conn@/\'s validation flags
-- 
-- /Since: 2.28/
tlsClientConnectionGetValidationFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
    a
    -- ^ /@conn@/: the t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> m [Gio.Flags.TlsCertificateFlags]
    -- ^ __Returns:__ the validation flags
tlsClientConnectionGetValidationFlags :: a -> m [TlsCertificateFlags]
tlsClientConnectionGetValidationFlags a
conn = IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TlsCertificateFlags] -> m [TlsCertificateFlags])
-> IO [TlsCertificateFlags] -> m [TlsCertificateFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    CUInt
result <- Ptr TlsClientConnection -> IO CUInt
g_tls_client_connection_get_validation_flags Ptr TlsClientConnection
conn'
    let result' :: [TlsCertificateFlags]
result' = CUInt -> [TlsCertificateFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    [TlsCertificateFlags] -> IO [TlsCertificateFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [TlsCertificateFlags]
result'

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionGetValidationFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.TlsCertificateFlags]), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionGetValidationFlagsMethodInfo a signature where
    overloadedMethod = tlsClientConnectionGetValidationFlags

#endif

-- method TlsClientConnection::set_server_identity
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "identity"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketConnectable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GSocketConnectable describing the expected server identity"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_client_connection_set_server_identity" g_tls_client_connection_set_server_identity :: 
    Ptr TlsClientConnection ->              -- conn : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    Ptr Gio.SocketConnectable.SocketConnectable -> -- identity : TInterface (Name {namespace = "Gio", name = "SocketConnectable"})
    IO ()

-- | Sets /@conn@/\'s expected server identity, which is used both to tell
-- servers on virtual hosts which certificate to present, and also
-- to let /@conn@/ know what name to look for in the certificate when
-- performing 'GI.Gio.Flags.TlsCertificateFlagsBadIdentity' validation, if enabled.
-- 
-- /Since: 2.28/
tlsClientConnectionSetServerIdentity ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a, Gio.SocketConnectable.IsSocketConnectable b) =>
    a
    -- ^ /@conn@/: the t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> b
    -- ^ /@identity@/: a t'GI.Gio.Interfaces.SocketConnectable.SocketConnectable' describing the expected server identity
    -> m ()
tlsClientConnectionSetServerIdentity :: a -> b -> m ()
tlsClientConnectionSetServerIdentity a
conn b
identity = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    Ptr SocketConnectable
identity' <- b -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
identity
    Ptr TlsClientConnection -> Ptr SocketConnectable -> IO ()
g_tls_client_connection_set_server_identity Ptr TlsClientConnection
conn' Ptr SocketConnectable
identity'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
identity
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionSetServerIdentityMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTlsClientConnection a, Gio.SocketConnectable.IsSocketConnectable b) => O.MethodInfo TlsClientConnectionSetServerIdentityMethodInfo a signature where
    overloadedMethod = tlsClientConnectionSetServerIdentity

#endif

-- method TlsClientConnection::set_use_ssl3
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_ssl3"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #gboolean, ignored"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_client_connection_set_use_ssl3" g_tls_client_connection_set_use_ssl3 :: 
    Ptr TlsClientConnection ->              -- conn : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    CInt ->                                 -- use_ssl3 : TBasicType TBoolean
    IO ()

{-# DEPRECATED tlsClientConnectionSetUseSsl3 ["(Since version 2.56)","SSL 3.0 is insecure."] #-}
-- | Since GLib 2.42.1, SSL 3.0 is no longer supported.
-- 
-- From GLib 2.42.1 through GLib 2.62, this function could be used to
-- force use of TLS 1.0, the lowest-supported TLS protocol version at
-- the time. In the past, this was needed to connect to broken TLS
-- servers that exhibited protocol version intolerance. Such servers
-- are no longer common, and using TLS 1.0 is no longer considered
-- acceptable.
-- 
-- Since GLib 2.64, this function does nothing.
-- 
-- /Since: 2.28/
tlsClientConnectionSetUseSsl3 ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
    a
    -- ^ /@conn@/: the t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> Bool
    -- ^ /@useSsl3@/: a t'P.Bool', ignored
    -> m ()
tlsClientConnectionSetUseSsl3 :: a -> Bool -> m ()
tlsClientConnectionSetUseSsl3 a
conn Bool
useSsl3 = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    let useSsl3' :: CInt
useSsl3' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
useSsl3
    Ptr TlsClientConnection -> CInt -> IO ()
g_tls_client_connection_set_use_ssl3 Ptr TlsClientConnection
conn' CInt
useSsl3'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionSetUseSsl3MethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionSetUseSsl3MethodInfo a signature where
    overloadedMethod = tlsClientConnectionSetUseSsl3

#endif

-- method TlsClientConnection::set_validation_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "conn"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsClientConnection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTlsClientConnection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "TlsCertificateFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTlsCertificateFlags to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_client_connection_set_validation_flags" g_tls_client_connection_set_validation_flags :: 
    Ptr TlsClientConnection ->              -- conn : TInterface (Name {namespace = "Gio", name = "TlsClientConnection"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "TlsCertificateFlags"})
    IO ()

-- | Sets /@conn@/\'s validation flags, to override the default set of
-- checks performed when validating a server certificate. By default,
-- 'GI.Gio.Flags.TlsCertificateFlagsValidateAll' is used.
-- 
-- /Since: 2.28/
tlsClientConnectionSetValidationFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsClientConnection a) =>
    a
    -- ^ /@conn@/: the t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection'
    -> [Gio.Flags.TlsCertificateFlags]
    -- ^ /@flags@/: the t'GI.Gio.Flags.TlsCertificateFlags' to use
    -> m ()
tlsClientConnectionSetValidationFlags :: a -> [TlsCertificateFlags] -> m ()
tlsClientConnectionSetValidationFlags a
conn [TlsCertificateFlags]
flags = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsClientConnection
conn' <- a -> IO (Ptr TlsClientConnection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
conn
    let flags' :: CUInt
flags' = [TlsCertificateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TlsCertificateFlags]
flags
    Ptr TlsClientConnection -> CUInt -> IO ()
g_tls_client_connection_set_validation_flags Ptr TlsClientConnection
conn' CUInt
flags'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
conn
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TlsClientConnectionSetValidationFlagsMethodInfo
instance (signature ~ ([Gio.Flags.TlsCertificateFlags] -> m ()), MonadIO m, IsTlsClientConnection a) => O.MethodInfo TlsClientConnectionSetValidationFlagsMethodInfo a signature where
    overloadedMethod = tlsClientConnectionSetValidationFlags

#endif

-- method TlsClientConnection::new
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "base_io_stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "IOStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GIOStream to wrap"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "server_identity"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SocketConnectable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the expected identity of the server"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "TlsClientConnection" })
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_client_connection_new" g_tls_client_connection_new :: 
    Ptr Gio.IOStream.IOStream ->            -- base_io_stream : TInterface (Name {namespace = "Gio", name = "IOStream"})
    Ptr Gio.SocketConnectable.SocketConnectable -> -- server_identity : TInterface (Name {namespace = "Gio", name = "SocketConnectable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr TlsClientConnection)

-- | Creates a new t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection' wrapping /@baseIoStream@/ (which
-- must have pollable input and output streams) which is assumed to
-- communicate with the server identified by /@serverIdentity@/.
-- 
-- See the documentation for t'GI.Gio.Objects.TlsConnection.TlsConnection':@/base-io-stream/@ for restrictions
-- on when application code can run operations on the /@baseIoStream@/ after
-- this function has returned.
-- 
-- /Since: 2.28/
tlsClientConnectionNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.IOStream.IsIOStream a, Gio.SocketConnectable.IsSocketConnectable b) =>
    a
    -- ^ /@baseIoStream@/: the t'GI.Gio.Objects.IOStream.IOStream' to wrap
    -> Maybe (b)
    -- ^ /@serverIdentity@/: the expected identity of the server
    -> m TlsClientConnection
    -- ^ __Returns:__ the new
    -- t'GI.Gio.Interfaces.TlsClientConnection.TlsClientConnection', or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
tlsClientConnectionNew :: a -> Maybe b -> m TlsClientConnection
tlsClientConnectionNew a
baseIoStream Maybe b
serverIdentity = IO TlsClientConnection -> m TlsClientConnection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsClientConnection -> m TlsClientConnection)
-> IO TlsClientConnection -> m TlsClientConnection
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 SocketConnectable
maybeServerIdentity <- case Maybe b
serverIdentity of
        Maybe b
Nothing -> Ptr SocketConnectable -> IO (Ptr SocketConnectable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketConnectable
forall a. Ptr a
nullPtr
        Just b
jServerIdentity -> do
            Ptr SocketConnectable
jServerIdentity' <- b -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jServerIdentity
            Ptr SocketConnectable -> IO (Ptr SocketConnectable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketConnectable
jServerIdentity'
    IO TlsClientConnection -> IO () -> IO TlsClientConnection
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr TlsClientConnection
result <- (Ptr (Ptr GError) -> IO (Ptr TlsClientConnection))
-> IO (Ptr TlsClientConnection)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr TlsClientConnection))
 -> IO (Ptr TlsClientConnection))
-> (Ptr (Ptr GError) -> IO (Ptr TlsClientConnection))
-> IO (Ptr TlsClientConnection)
forall a b. (a -> b) -> a -> b
$ Ptr IOStream
-> Ptr SocketConnectable
-> Ptr (Ptr GError)
-> IO (Ptr TlsClientConnection)
g_tls_client_connection_new Ptr IOStream
baseIoStream' Ptr SocketConnectable
maybeServerIdentity
        Text -> Ptr TlsClientConnection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsClientConnectionNew" Ptr TlsClientConnection
result
        TlsClientConnection
result' <- ((ManagedPtr TlsClientConnection -> TlsClientConnection)
-> Ptr TlsClientConnection -> IO TlsClientConnection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsClientConnection -> TlsClientConnection
TlsClientConnection) Ptr TlsClientConnection
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
serverIdentity b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        TlsClientConnection -> IO TlsClientConnection
forall (m :: * -> *) a. Monad m => a -> m a
return TlsClientConnection
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 TlsClientConnection = TlsClientConnectionSignalList
type TlsClientConnectionSignalList = ('[ '("acceptCertificate", Gio.TlsConnection.TlsConnectionAcceptCertificateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif