{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A certificate used for TLS authentication and encryption.
-- This can represent either a certificate only (eg, the certificate
-- received by a client from a server), or the combination of
-- a certificate and a private key (which is needed when acting as a
-- t'GI.Gio.Interfaces.TlsServerConnection.TlsServerConnection').
-- 
-- /Since: 2.28/

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

module GI.Gio.Objects.TlsCertificate
    ( 

-- * Exported types
    TlsCertificate(..)                      ,
    IsTlsCertificate                        ,
    toTlsCertificate                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isSame]("GI.Gio.Objects.TlsCertificate#g:method:isSame"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [verify]("GI.Gio.Objects.TlsCertificate#g:method:verify"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDnsNames]("GI.Gio.Objects.TlsCertificate#g:method:getDnsNames"), [getIpAddresses]("GI.Gio.Objects.TlsCertificate#g:method:getIpAddresses"), [getIssuer]("GI.Gio.Objects.TlsCertificate#g:method:getIssuer"), [getIssuerName]("GI.Gio.Objects.TlsCertificate#g:method:getIssuerName"), [getNotValidAfter]("GI.Gio.Objects.TlsCertificate#g:method:getNotValidAfter"), [getNotValidBefore]("GI.Gio.Objects.TlsCertificate#g:method:getNotValidBefore"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSubjectName]("GI.Gio.Objects.TlsCertificate#g:method:getSubjectName").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveTlsCertificateMethod             ,
#endif

-- ** getDnsNames #method:getDnsNames#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateGetDnsNamesMethodInfo     ,
#endif
    tlsCertificateGetDnsNames               ,


-- ** getIpAddresses #method:getIpAddresses#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateGetIpAddressesMethodInfo  ,
#endif
    tlsCertificateGetIpAddresses            ,


-- ** getIssuer #method:getIssuer#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateGetIssuerMethodInfo       ,
#endif
    tlsCertificateGetIssuer                 ,


-- ** getIssuerName #method:getIssuerName#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateGetIssuerNameMethodInfo   ,
#endif
    tlsCertificateGetIssuerName             ,


-- ** getNotValidAfter #method:getNotValidAfter#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateGetNotValidAfterMethodInfo,
#endif
    tlsCertificateGetNotValidAfter          ,


-- ** getNotValidBefore #method:getNotValidBefore#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateGetNotValidBeforeMethodInfo,
#endif
    tlsCertificateGetNotValidBefore         ,


-- ** getSubjectName #method:getSubjectName#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateGetSubjectNameMethodInfo  ,
#endif
    tlsCertificateGetSubjectName            ,


-- ** isSame #method:isSame#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateIsSameMethodInfo          ,
#endif
    tlsCertificateIsSame                    ,


-- ** listNewFromFile #method:listNewFromFile#

    tlsCertificateListNewFromFile           ,


-- ** newFromFile #method:newFromFile#

    tlsCertificateNewFromFile               ,


-- ** newFromFiles #method:newFromFiles#

    tlsCertificateNewFromFiles              ,


-- ** newFromPem #method:newFromPem#

    tlsCertificateNewFromPem                ,


-- ** newFromPkcs11Uris #method:newFromPkcs11Uris#

    tlsCertificateNewFromPkcs11Uris         ,


-- ** verify #method:verify#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateVerifyMethodInfo          ,
#endif
    tlsCertificateVerify                    ,




 -- * Properties


-- ** certificate #attr:certificate#
-- | The DER (binary) encoded representation of the certificate.
-- This property and the [TlsCertificate:certificatePem]("GI.Gio.Objects.TlsCertificate#g:attr:certificatePem") property
-- represent the same data, just in different forms.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsCertificateCertificatePropertyInfo   ,
#endif
    constructTlsCertificateCertificate      ,
    getTlsCertificateCertificate            ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificateCertificate               ,
#endif


-- ** certificatePem #attr:certificatePem#
-- | The PEM (ASCII) encoded representation of the certificate.
-- This property and the [TlsCertificate:certificate]("GI.Gio.Objects.TlsCertificate#g:attr:certificate")
-- property represent the same data, just in different forms.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsCertificateCertificatePemPropertyInfo,
#endif
    constructTlsCertificateCertificatePem   ,
    getTlsCertificateCertificatePem         ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificateCertificatePem            ,
#endif


-- ** dnsNames #attr:dnsNames#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateDnsNamesPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    tlsCertificateDnsNames                  ,
#endif


-- ** ipAddresses #attr:ipAddresses#

#if defined(ENABLE_OVERLOADING)
    TlsCertificateIpAddressesPropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    tlsCertificateIpAddresses               ,
#endif


-- ** issuer #attr:issuer#
-- | A t'GI.Gio.Objects.TlsCertificate.TlsCertificate' representing the entity that issued this
-- certificate. If 'P.Nothing', this means that the certificate is either
-- self-signed, or else the certificate of the issuer is not
-- available.
-- 
-- Beware the issuer certificate may not be the same as the
-- certificate that would actually be used to construct a valid
-- certification path during certificate verification.
-- <https://datatracker.ietf.org/doc/html/rfc4158 RFC 4158> explains
-- why an issuer certificate cannot be naively assumed to be part of the
-- the certification path (though GLib\'s TLS backends may not follow the
-- path building strategies outlined in this RFC). Due to the complexity
-- of certification path building, GLib does not provide any way to know
-- which certification path will actually be used. Accordingly, this
-- property cannot be used to make security-related decisions. Only
-- GLib itself should make security decisions about TLS certificates.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsCertificateIssuerPropertyInfo        ,
#endif
    constructTlsCertificateIssuer           ,
    getTlsCertificateIssuer                 ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificateIssuer                    ,
#endif


-- ** issuerName #attr:issuerName#
-- | The issuer from the certificate,
-- 'P.Nothing' if unavailable.
-- 
-- /Since: 2.70/

#if defined(ENABLE_OVERLOADING)
    TlsCertificateIssuerNamePropertyInfo    ,
#endif
    getTlsCertificateIssuerName             ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificateIssuerName                ,
#endif


-- ** notValidAfter #attr:notValidAfter#
-- | The time at which this cert is no longer valid,
-- 'P.Nothing' if unavailable.
-- 
-- /Since: 2.70/

#if defined(ENABLE_OVERLOADING)
    TlsCertificateNotValidAfterPropertyInfo ,
#endif
    getTlsCertificateNotValidAfter          ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificateNotValidAfter             ,
#endif


-- ** notValidBefore #attr:notValidBefore#
-- | The time at which this cert is considered to be valid,
-- 'P.Nothing' if unavailable.
-- 
-- /Since: 2.70/

#if defined(ENABLE_OVERLOADING)
    TlsCertificateNotValidBeforePropertyInfo,
#endif
    getTlsCertificateNotValidBefore         ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificateNotValidBefore            ,
#endif


-- ** pkcs11Uri #attr:pkcs11Uri#
-- | A URI referencing the <https://docs.oasis-open.org/pkcs11/pkcs11-base/v3.0/os/pkcs11-base-v3.0-os.html PKCS \#11>
-- objects containing an X.509 certificate and optionally a private key.
-- 
-- If 'P.Nothing', the certificate is either not backed by PKCS #11 or the
-- t'GI.Gio.Interfaces.TlsBackend.TlsBackend' does not support PKCS #11.
-- 
-- /Since: 2.68/

#if defined(ENABLE_OVERLOADING)
    TlsCertificatePkcs11UriPropertyInfo     ,
#endif
    constructTlsCertificatePkcs11Uri        ,
    getTlsCertificatePkcs11Uri              ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificatePkcs11Uri                 ,
#endif


-- ** privateKey #attr:privateKey#
-- | The DER (binary) encoded representation of the certificate\'s
-- private key, in either <https://datatracker.ietf.org/doc/html/rfc8017 PKCS \#1 format>
-- or unencrypted <https://datatracker.ietf.org/doc/html/rfc5208 PKCS \#8 format.>
-- PKCS #8 format is supported since 2.32; earlier releases only
-- support PKCS #1. You can use the @openssl rsa@ tool to convert
-- PKCS #8 keys to PKCS #1.
-- 
-- This property (or the [TlsCertificate:privateKeyPem]("GI.Gio.Objects.TlsCertificate#g:attr:privateKeyPem") property)
-- can be set when constructing a key (for example, from a file).
-- Since GLib 2.70, it is now also readable; however, be aware that if
-- the private key is backed by a PKCS #11 URI – for example, if it
-- is stored on a smartcard – then this property will be 'P.Nothing'. If so,
-- the private key must be referenced via its PKCS #11 URI,
-- [TlsCertificate:privateKeyPkcs11Uri]("GI.Gio.Objects.TlsCertificate#g:attr:privateKeyPkcs11Uri"). You must check both
-- properties to see if the certificate really has a private key.
-- When this property is read, the output format will be unencrypted
-- PKCS #8.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsCertificatePrivateKeyPropertyInfo    ,
#endif
    constructTlsCertificatePrivateKey       ,
    getTlsCertificatePrivateKey             ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificatePrivateKey                ,
#endif


-- ** privateKeyPem #attr:privateKeyPem#
-- | The PEM (ASCII) encoded representation of the certificate\'s
-- private key in either <https://datatracker.ietf.org/doc/html/rfc8017 PKCS \#1 format>
-- (\"@BEGIN RSA PRIVATE KEY@\") or unencrypted
-- <https://datatracker.ietf.org/doc/html/rfc5208 PKCS \#8 format>
-- (\"@BEGIN PRIVATE KEY@\"). PKCS #8 format is supported since 2.32;
-- earlier releases only support PKCS #1. You can use the @openssl rsa@
-- tool to convert PKCS #8 keys to PKCS #1.
-- 
-- This property (or the [TlsCertificate:privateKey]("GI.Gio.Objects.TlsCertificate#g:attr:privateKey") property)
-- can be set when constructing a key (for example, from a file).
-- Since GLib 2.70, it is now also readable; however, be aware that if
-- the private key is backed by a PKCS #11 URI - for example, if it
-- is stored on a smartcard - then this property will be 'P.Nothing'. If so,
-- the private key must be referenced via its PKCS #11 URI,
-- [TlsCertificate:privateKeyPkcs11Uri]("GI.Gio.Objects.TlsCertificate#g:attr:privateKeyPkcs11Uri"). You must check both
-- properties to see if the certificate really has a private key.
-- When this property is read, the output format will be unencrypted
-- PKCS #8.
-- 
-- /Since: 2.28/

#if defined(ENABLE_OVERLOADING)
    TlsCertificatePrivateKeyPemPropertyInfo ,
#endif
    constructTlsCertificatePrivateKeyPem    ,
    getTlsCertificatePrivateKeyPem          ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificatePrivateKeyPem             ,
#endif


-- ** privateKeyPkcs11Uri #attr:privateKeyPkcs11Uri#
-- | A URI referencing a <https://docs.oasis-open.org/pkcs11/pkcs11-base/v3.0/os/pkcs11-base-v3.0-os.html PKCS \#11>
-- object containing a private key.
-- 
-- /Since: 2.68/

#if defined(ENABLE_OVERLOADING)
    TlsCertificatePrivateKeyPkcs11UriPropertyInfo,
#endif
    constructTlsCertificatePrivateKeyPkcs11Uri,
    getTlsCertificatePrivateKeyPkcs11Uri    ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificatePrivateKeyPkcs11Uri       ,
#endif


-- ** subjectName #attr:subjectName#
-- | The subject from the cert,
-- 'P.Nothing' if unavailable.
-- 
-- /Since: 2.70/

#if defined(ENABLE_OVERLOADING)
    TlsCertificateSubjectNamePropertyInfo   ,
#endif
    getTlsCertificateSubjectName            ,
#if defined(ENABLE_OVERLOADING)
    tlsCertificateSubjectName               ,
#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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
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.InetAddress as Gio.InetAddress

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

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

foreign import ccall "g_tls_certificate_get_type"
    c_g_tls_certificate_get_type :: IO B.Types.GType

instance B.Types.TypedObject TlsCertificate where
    glibType :: IO GType
glibType = IO GType
c_g_tls_certificate_get_type

instance B.Types.GObject TlsCertificate

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

instance O.HasParentTypes TlsCertificate
type instance O.ParentTypes TlsCertificate = '[GObject.Object.Object]

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

-- | Convert 'TlsCertificate' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe TlsCertificate) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_tls_certificate_get_type
    gvalueSet_ :: Ptr GValue -> Maybe TlsCertificate -> IO ()
gvalueSet_ Ptr GValue
gv Maybe TlsCertificate
P.Nothing = Ptr GValue -> Ptr TlsCertificate -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr TlsCertificate
forall a. Ptr a
FP.nullPtr :: FP.Ptr TlsCertificate)
    gvalueSet_ Ptr GValue
gv (P.Just TlsCertificate
obj) = TlsCertificate -> (Ptr TlsCertificate -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsCertificate
obj (Ptr GValue -> Ptr TlsCertificate -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe TlsCertificate)
gvalueGet_ Ptr GValue
gv = do
        Ptr TlsCertificate
ptr <- Ptr GValue -> IO (Ptr TlsCertificate)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr TlsCertificate)
        if Ptr TlsCertificate
ptr Ptr TlsCertificate -> Ptr TlsCertificate -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TlsCertificate
forall a. Ptr a
FP.nullPtr
        then TlsCertificate -> Maybe TlsCertificate
forall a. a -> Maybe a
P.Just (TlsCertificate -> Maybe TlsCertificate)
-> IO TlsCertificate -> IO (Maybe TlsCertificate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate Ptr TlsCertificate
ptr
        else Maybe TlsCertificate -> IO (Maybe TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsCertificate
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveTlsCertificateMethod (t :: Symbol) (o :: *) :: * where
    ResolveTlsCertificateMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTlsCertificateMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTlsCertificateMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTlsCertificateMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTlsCertificateMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTlsCertificateMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTlsCertificateMethod "isSame" o = TlsCertificateIsSameMethodInfo
    ResolveTlsCertificateMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTlsCertificateMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTlsCertificateMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTlsCertificateMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTlsCertificateMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTlsCertificateMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTlsCertificateMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTlsCertificateMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTlsCertificateMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTlsCertificateMethod "verify" o = TlsCertificateVerifyMethodInfo
    ResolveTlsCertificateMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTlsCertificateMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTlsCertificateMethod "getDnsNames" o = TlsCertificateGetDnsNamesMethodInfo
    ResolveTlsCertificateMethod "getIpAddresses" o = TlsCertificateGetIpAddressesMethodInfo
    ResolveTlsCertificateMethod "getIssuer" o = TlsCertificateGetIssuerMethodInfo
    ResolveTlsCertificateMethod "getIssuerName" o = TlsCertificateGetIssuerNameMethodInfo
    ResolveTlsCertificateMethod "getNotValidAfter" o = TlsCertificateGetNotValidAfterMethodInfo
    ResolveTlsCertificateMethod "getNotValidBefore" o = TlsCertificateGetNotValidBeforeMethodInfo
    ResolveTlsCertificateMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTlsCertificateMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTlsCertificateMethod "getSubjectName" o = TlsCertificateGetSubjectNameMethodInfo
    ResolveTlsCertificateMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTlsCertificateMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTlsCertificateMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTlsCertificateMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTlsCertificateMethod t TlsCertificate, O.OverloadedMethod info TlsCertificate p, R.HasField t TlsCertificate p) => R.HasField t TlsCertificate p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "certificate"
   -- Type: TByteArray
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@certificate@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #certificate
-- @
getTlsCertificateCertificate :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe ByteString)
getTlsCertificateCertificate :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe ByteString)
getTlsCertificateCertificate o
obj = IO (Maybe ByteString) -> m (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe ByteString) -> m (Maybe ByteString))
-> IO (Maybe ByteString) -> m (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe ByteString)
forall a. GObject a => a -> String -> IO (Maybe ByteString)
B.Properties.getObjectPropertyByteArray o
obj String
"certificate"

-- | Construct a `GValueConstruct` with valid value for the “@certificate@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsCertificateCertificate :: (IsTlsCertificate o, MIO.MonadIO m) => ByteString -> m (GValueConstruct o)
constructTlsCertificateCertificate :: forall o (m :: * -> *).
(IsTlsCertificate o, MonadIO m) =>
ByteString -> m (GValueConstruct o)
constructTlsCertificateCertificate ByteString
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe ByteString -> IO (GValueConstruct o)
forall o. String -> Maybe ByteString -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyByteArray String
"certificate" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
P.Just ByteString
val)

#if defined(ENABLE_OVERLOADING)
data TlsCertificateCertificatePropertyInfo
instance AttrInfo TlsCertificateCertificatePropertyInfo where
    type AttrAllowedOps TlsCertificateCertificatePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificateCertificatePropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificateCertificatePropertyInfo = (~) ByteString
    type AttrTransferTypeConstraint TlsCertificateCertificatePropertyInfo = (~) ByteString
    type AttrTransferType TlsCertificateCertificatePropertyInfo = ByteString
    type AttrGetType TlsCertificateCertificatePropertyInfo = (Maybe ByteString)
    type AttrLabel TlsCertificateCertificatePropertyInfo = "certificate"
    type AttrOrigin TlsCertificateCertificatePropertyInfo = TlsCertificate
    attrGet = getTlsCertificateCertificate
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructTlsCertificateCertificate
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.certificate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:certificate"
        })
#endif

-- VVV Prop "certificate-pem"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@certificate-pem@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #certificatePem
-- @
getTlsCertificateCertificatePem :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe T.Text)
getTlsCertificateCertificatePem :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe Text)
getTlsCertificateCertificatePem o
obj = IO (Maybe Text) -> m (Maybe Text)
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
"certificate-pem"

-- | Construct a `GValueConstruct` with valid value for the “@certificate-pem@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsCertificateCertificatePem :: (IsTlsCertificate o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTlsCertificateCertificatePem :: forall o (m :: * -> *).
(IsTlsCertificate o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructTlsCertificateCertificatePem Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"certificate-pem" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data TlsCertificateCertificatePemPropertyInfo
instance AttrInfo TlsCertificateCertificatePemPropertyInfo where
    type AttrAllowedOps TlsCertificateCertificatePemPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificateCertificatePemPropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificateCertificatePemPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint TlsCertificateCertificatePemPropertyInfo = (~) T.Text
    type AttrTransferType TlsCertificateCertificatePemPropertyInfo = T.Text
    type AttrGetType TlsCertificateCertificatePemPropertyInfo = (Maybe T.Text)
    type AttrLabel TlsCertificateCertificatePemPropertyInfo = "certificate-pem"
    type AttrOrigin TlsCertificateCertificatePemPropertyInfo = TlsCertificate
    attrGet = getTlsCertificateCertificatePem
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructTlsCertificateCertificatePem
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.certificatePem"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:certificatePem"
        })
#endif

-- XXX Generation of property "dns-names" of object "TlsCertificate" failed.
-- Not implemented: Property TlsCertificateDnsNames has unsupported transfer type TransferContainer
#if defined(ENABLE_OVERLOADING)
-- XXX Placeholder
data TlsCertificateDnsNamesPropertyInfo
instance AttrInfo TlsCertificateDnsNamesPropertyInfo where
    type AttrAllowedOps TlsCertificateDnsNamesPropertyInfo = '[]
    type AttrSetTypeConstraint TlsCertificateDnsNamesPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsCertificateDnsNamesPropertyInfo = (~) ()
    type AttrTransferType TlsCertificateDnsNamesPropertyInfo = ()
    type AttrBaseTypeConstraint TlsCertificateDnsNamesPropertyInfo = (~) ()
    type AttrGetType TlsCertificateDnsNamesPropertyInfo = ()
    type AttrLabel TlsCertificateDnsNamesPropertyInfo = ""
    type AttrOrigin TlsCertificateDnsNamesPropertyInfo = TlsCertificate
    attrGet = undefined
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
#endif

-- XXX Generation of property "ip-addresses" of object "TlsCertificate" failed.
-- Not implemented: Property TlsCertificateIpAddresses has unsupported transfer type TransferContainer
#if defined(ENABLE_OVERLOADING)
-- XXX Placeholder
data TlsCertificateIpAddressesPropertyInfo
instance AttrInfo TlsCertificateIpAddressesPropertyInfo where
    type AttrAllowedOps TlsCertificateIpAddressesPropertyInfo = '[]
    type AttrSetTypeConstraint TlsCertificateIpAddressesPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsCertificateIpAddressesPropertyInfo = (~) ()
    type AttrTransferType TlsCertificateIpAddressesPropertyInfo = ()
    type AttrBaseTypeConstraint TlsCertificateIpAddressesPropertyInfo = (~) ()
    type AttrGetType TlsCertificateIpAddressesPropertyInfo = ()
    type AttrLabel TlsCertificateIpAddressesPropertyInfo = ""
    type AttrOrigin TlsCertificateIpAddressesPropertyInfo = TlsCertificate
    attrGet = undefined
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
#endif

-- VVV Prop "issuer"
   -- Type: TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@issuer@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #issuer
-- @
getTlsCertificateIssuer :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe TlsCertificate)
getTlsCertificateIssuer :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe TlsCertificate)
getTlsCertificateIssuer o
obj = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
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
"issuer" ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate

-- | Construct a `GValueConstruct` with valid value for the “@issuer@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsCertificateIssuer :: (IsTlsCertificate o, MIO.MonadIO m, IsTlsCertificate a) => a -> m (GValueConstruct o)
constructTlsCertificateIssuer :: forall o (m :: * -> *) a.
(IsTlsCertificate o, MonadIO m, IsTlsCertificate a) =>
a -> m (GValueConstruct o)
constructTlsCertificateIssuer 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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"issuer" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data TlsCertificateIssuerPropertyInfo
instance AttrInfo TlsCertificateIssuerPropertyInfo where
    type AttrAllowedOps TlsCertificateIssuerPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificateIssuerPropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificateIssuerPropertyInfo = IsTlsCertificate
    type AttrTransferTypeConstraint TlsCertificateIssuerPropertyInfo = IsTlsCertificate
    type AttrTransferType TlsCertificateIssuerPropertyInfo = TlsCertificate
    type AttrGetType TlsCertificateIssuerPropertyInfo = (Maybe TlsCertificate)
    type AttrLabel TlsCertificateIssuerPropertyInfo = "issuer"
    type AttrOrigin TlsCertificateIssuerPropertyInfo = TlsCertificate
    attrGet = getTlsCertificateIssuer
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo TlsCertificate v
    attrConstruct = constructTlsCertificateIssuer
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.issuer"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:issuer"
        })
#endif

-- VVV Prop "issuer-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@issuer-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #issuerName
-- @
getTlsCertificateIssuerName :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe T.Text)
getTlsCertificateIssuerName :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe Text)
getTlsCertificateIssuerName o
obj = IO (Maybe Text) -> m (Maybe Text)
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
"issuer-name"

#if defined(ENABLE_OVERLOADING)
data TlsCertificateIssuerNamePropertyInfo
instance AttrInfo TlsCertificateIssuerNamePropertyInfo where
    type AttrAllowedOps TlsCertificateIssuerNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificateIssuerNamePropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificateIssuerNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsCertificateIssuerNamePropertyInfo = (~) ()
    type AttrTransferType TlsCertificateIssuerNamePropertyInfo = ()
    type AttrGetType TlsCertificateIssuerNamePropertyInfo = (Maybe T.Text)
    type AttrLabel TlsCertificateIssuerNamePropertyInfo = "issuer-name"
    type AttrOrigin TlsCertificateIssuerNamePropertyInfo = TlsCertificate
    attrGet = getTlsCertificateIssuerName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.issuerName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:issuerName"
        })
#endif

-- VVV Prop "not-valid-after"
   -- Type: TInterface (Name {namespace = "GLib", name = "DateTime"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@not-valid-after@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #notValidAfter
-- @
getTlsCertificateNotValidAfter :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe GLib.DateTime.DateTime)
getTlsCertificateNotValidAfter :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe DateTime)
getTlsCertificateNotValidAfter o
obj = IO (Maybe DateTime) -> m (Maybe DateTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DateTime) -> m (Maybe DateTime))
-> IO (Maybe DateTime) -> m (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DateTime -> DateTime)
-> IO (Maybe DateTime)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"not-valid-after" ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime

#if defined(ENABLE_OVERLOADING)
data TlsCertificateNotValidAfterPropertyInfo
instance AttrInfo TlsCertificateNotValidAfterPropertyInfo where
    type AttrAllowedOps TlsCertificateNotValidAfterPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificateNotValidAfterPropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificateNotValidAfterPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsCertificateNotValidAfterPropertyInfo = (~) ()
    type AttrTransferType TlsCertificateNotValidAfterPropertyInfo = ()
    type AttrGetType TlsCertificateNotValidAfterPropertyInfo = (Maybe GLib.DateTime.DateTime)
    type AttrLabel TlsCertificateNotValidAfterPropertyInfo = "not-valid-after"
    type AttrOrigin TlsCertificateNotValidAfterPropertyInfo = TlsCertificate
    attrGet = getTlsCertificateNotValidAfter
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.notValidAfter"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:notValidAfter"
        })
#endif

-- VVV Prop "not-valid-before"
   -- Type: TInterface (Name {namespace = "GLib", name = "DateTime"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@not-valid-before@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #notValidBefore
-- @
getTlsCertificateNotValidBefore :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe GLib.DateTime.DateTime)
getTlsCertificateNotValidBefore :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe DateTime)
getTlsCertificateNotValidBefore o
obj = IO (Maybe DateTime) -> m (Maybe DateTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DateTime) -> m (Maybe DateTime))
-> IO (Maybe DateTime) -> m (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DateTime -> DateTime)
-> IO (Maybe DateTime)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"not-valid-before" ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime

#if defined(ENABLE_OVERLOADING)
data TlsCertificateNotValidBeforePropertyInfo
instance AttrInfo TlsCertificateNotValidBeforePropertyInfo where
    type AttrAllowedOps TlsCertificateNotValidBeforePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificateNotValidBeforePropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificateNotValidBeforePropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsCertificateNotValidBeforePropertyInfo = (~) ()
    type AttrTransferType TlsCertificateNotValidBeforePropertyInfo = ()
    type AttrGetType TlsCertificateNotValidBeforePropertyInfo = (Maybe GLib.DateTime.DateTime)
    type AttrLabel TlsCertificateNotValidBeforePropertyInfo = "not-valid-before"
    type AttrOrigin TlsCertificateNotValidBeforePropertyInfo = TlsCertificate
    attrGet = getTlsCertificateNotValidBefore
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.notValidBefore"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:notValidBefore"
        })
#endif

-- VVV Prop "pkcs11-uri"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@pkcs11-uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #pkcs11Uri
-- @
getTlsCertificatePkcs11Uri :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe T.Text)
getTlsCertificatePkcs11Uri :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe Text)
getTlsCertificatePkcs11Uri o
obj = IO (Maybe Text) -> m (Maybe Text)
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
"pkcs11-uri"

-- | Construct a `GValueConstruct` with valid value for the “@pkcs11-uri@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsCertificatePkcs11Uri :: (IsTlsCertificate o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTlsCertificatePkcs11Uri :: forall o (m :: * -> *).
(IsTlsCertificate o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructTlsCertificatePkcs11Uri Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"pkcs11-uri" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data TlsCertificatePkcs11UriPropertyInfo
instance AttrInfo TlsCertificatePkcs11UriPropertyInfo where
    type AttrAllowedOps TlsCertificatePkcs11UriPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificatePkcs11UriPropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificatePkcs11UriPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint TlsCertificatePkcs11UriPropertyInfo = (~) T.Text
    type AttrTransferType TlsCertificatePkcs11UriPropertyInfo = T.Text
    type AttrGetType TlsCertificatePkcs11UriPropertyInfo = (Maybe T.Text)
    type AttrLabel TlsCertificatePkcs11UriPropertyInfo = "pkcs11-uri"
    type AttrOrigin TlsCertificatePkcs11UriPropertyInfo = TlsCertificate
    attrGet = getTlsCertificatePkcs11Uri
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructTlsCertificatePkcs11Uri
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.pkcs11Uri"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:pkcs11Uri"
        })
#endif

-- VVV Prop "private-key"
   -- Type: TByteArray
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@private-key@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #privateKey
-- @
getTlsCertificatePrivateKey :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe ByteString)
getTlsCertificatePrivateKey :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe ByteString)
getTlsCertificatePrivateKey o
obj = IO (Maybe ByteString) -> m (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe ByteString) -> m (Maybe ByteString))
-> IO (Maybe ByteString) -> m (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe ByteString)
forall a. GObject a => a -> String -> IO (Maybe ByteString)
B.Properties.getObjectPropertyByteArray o
obj String
"private-key"

-- | Construct a `GValueConstruct` with valid value for the “@private-key@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsCertificatePrivateKey :: (IsTlsCertificate o, MIO.MonadIO m) => ByteString -> m (GValueConstruct o)
constructTlsCertificatePrivateKey :: forall o (m :: * -> *).
(IsTlsCertificate o, MonadIO m) =>
ByteString -> m (GValueConstruct o)
constructTlsCertificatePrivateKey ByteString
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe ByteString -> IO (GValueConstruct o)
forall o. String -> Maybe ByteString -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyByteArray String
"private-key" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
P.Just ByteString
val)

#if defined(ENABLE_OVERLOADING)
data TlsCertificatePrivateKeyPropertyInfo
instance AttrInfo TlsCertificatePrivateKeyPropertyInfo where
    type AttrAllowedOps TlsCertificatePrivateKeyPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificatePrivateKeyPropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificatePrivateKeyPropertyInfo = (~) ByteString
    type AttrTransferTypeConstraint TlsCertificatePrivateKeyPropertyInfo = (~) ByteString
    type AttrTransferType TlsCertificatePrivateKeyPropertyInfo = ByteString
    type AttrGetType TlsCertificatePrivateKeyPropertyInfo = (Maybe ByteString)
    type AttrLabel TlsCertificatePrivateKeyPropertyInfo = "private-key"
    type AttrOrigin TlsCertificatePrivateKeyPropertyInfo = TlsCertificate
    attrGet = getTlsCertificatePrivateKey
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructTlsCertificatePrivateKey
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.privateKey"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:privateKey"
        })
#endif

-- VVV Prop "private-key-pem"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@private-key-pem@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #privateKeyPem
-- @
getTlsCertificatePrivateKeyPem :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe T.Text)
getTlsCertificatePrivateKeyPem :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe Text)
getTlsCertificatePrivateKeyPem o
obj = IO (Maybe Text) -> m (Maybe Text)
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
"private-key-pem"

-- | Construct a `GValueConstruct` with valid value for the “@private-key-pem@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsCertificatePrivateKeyPem :: (IsTlsCertificate o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTlsCertificatePrivateKeyPem :: forall o (m :: * -> *).
(IsTlsCertificate o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructTlsCertificatePrivateKeyPem Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"private-key-pem" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data TlsCertificatePrivateKeyPemPropertyInfo
instance AttrInfo TlsCertificatePrivateKeyPemPropertyInfo where
    type AttrAllowedOps TlsCertificatePrivateKeyPemPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificatePrivateKeyPemPropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificatePrivateKeyPemPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint TlsCertificatePrivateKeyPemPropertyInfo = (~) T.Text
    type AttrTransferType TlsCertificatePrivateKeyPemPropertyInfo = T.Text
    type AttrGetType TlsCertificatePrivateKeyPemPropertyInfo = (Maybe T.Text)
    type AttrLabel TlsCertificatePrivateKeyPemPropertyInfo = "private-key-pem"
    type AttrOrigin TlsCertificatePrivateKeyPemPropertyInfo = TlsCertificate
    attrGet = getTlsCertificatePrivateKeyPem
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructTlsCertificatePrivateKeyPem
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.privateKeyPem"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:privateKeyPem"
        })
#endif

-- VVV Prop "private-key-pkcs11-uri"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@private-key-pkcs11-uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #privateKeyPkcs11Uri
-- @
getTlsCertificatePrivateKeyPkcs11Uri :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe T.Text)
getTlsCertificatePrivateKeyPkcs11Uri :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe Text)
getTlsCertificatePrivateKeyPkcs11Uri o
obj = IO (Maybe Text) -> m (Maybe Text)
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
"private-key-pkcs11-uri"

-- | Construct a `GValueConstruct` with valid value for the “@private-key-pkcs11-uri@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsCertificatePrivateKeyPkcs11Uri :: (IsTlsCertificate o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTlsCertificatePrivateKeyPkcs11Uri :: forall o (m :: * -> *).
(IsTlsCertificate o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructTlsCertificatePrivateKeyPkcs11Uri Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"private-key-pkcs11-uri" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data TlsCertificatePrivateKeyPkcs11UriPropertyInfo
instance AttrInfo TlsCertificatePrivateKeyPkcs11UriPropertyInfo where
    type AttrAllowedOps TlsCertificatePrivateKeyPkcs11UriPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificatePrivateKeyPkcs11UriPropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificatePrivateKeyPkcs11UriPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint TlsCertificatePrivateKeyPkcs11UriPropertyInfo = (~) T.Text
    type AttrTransferType TlsCertificatePrivateKeyPkcs11UriPropertyInfo = T.Text
    type AttrGetType TlsCertificatePrivateKeyPkcs11UriPropertyInfo = (Maybe T.Text)
    type AttrLabel TlsCertificatePrivateKeyPkcs11UriPropertyInfo = "private-key-pkcs11-uri"
    type AttrOrigin TlsCertificatePrivateKeyPkcs11UriPropertyInfo = TlsCertificate
    attrGet = getTlsCertificatePrivateKeyPkcs11Uri
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructTlsCertificatePrivateKeyPkcs11Uri
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.privateKeyPkcs11Uri"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:privateKeyPkcs11Uri"
        })
#endif

-- VVV Prop "subject-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@subject-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsCertificate #subjectName
-- @
getTlsCertificateSubjectName :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe T.Text)
getTlsCertificateSubjectName :: forall (m :: * -> *) o.
(MonadIO m, IsTlsCertificate o) =>
o -> m (Maybe Text)
getTlsCertificateSubjectName o
obj = IO (Maybe Text) -> m (Maybe Text)
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
"subject-name"

#if defined(ENABLE_OVERLOADING)
data TlsCertificateSubjectNamePropertyInfo
instance AttrInfo TlsCertificateSubjectNamePropertyInfo where
    type AttrAllowedOps TlsCertificateSubjectNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TlsCertificateSubjectNamePropertyInfo = IsTlsCertificate
    type AttrSetTypeConstraint TlsCertificateSubjectNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint TlsCertificateSubjectNamePropertyInfo = (~) ()
    type AttrTransferType TlsCertificateSubjectNamePropertyInfo = ()
    type AttrGetType TlsCertificateSubjectNamePropertyInfo = (Maybe T.Text)
    type AttrLabel TlsCertificateSubjectNamePropertyInfo = "subject-name"
    type AttrOrigin TlsCertificateSubjectNamePropertyInfo = TlsCertificate
    attrGet = getTlsCertificateSubjectName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.subjectName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#g:attr:subjectName"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsCertificate
type instance O.AttributeList TlsCertificate = TlsCertificateAttributeList
type TlsCertificateAttributeList = ('[ '("certificate", TlsCertificateCertificatePropertyInfo), '("certificatePem", TlsCertificateCertificatePemPropertyInfo), '("dnsNames", TlsCertificateDnsNamesPropertyInfo), '("ipAddresses", TlsCertificateIpAddressesPropertyInfo), '("issuer", TlsCertificateIssuerPropertyInfo), '("issuerName", TlsCertificateIssuerNamePropertyInfo), '("notValidAfter", TlsCertificateNotValidAfterPropertyInfo), '("notValidBefore", TlsCertificateNotValidBeforePropertyInfo), '("pkcs11Uri", TlsCertificatePkcs11UriPropertyInfo), '("privateKey", TlsCertificatePrivateKeyPropertyInfo), '("privateKeyPem", TlsCertificatePrivateKeyPemPropertyInfo), '("privateKeyPkcs11Uri", TlsCertificatePrivateKeyPkcs11UriPropertyInfo), '("subjectName", TlsCertificateSubjectNamePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
tlsCertificateCertificate :: AttrLabelProxy "certificate"
tlsCertificateCertificate = AttrLabelProxy

tlsCertificateCertificatePem :: AttrLabelProxy "certificatePem"
tlsCertificateCertificatePem = AttrLabelProxy

tlsCertificateDnsNames :: AttrLabelProxy "dnsNames"
tlsCertificateDnsNames = AttrLabelProxy

tlsCertificateIpAddresses :: AttrLabelProxy "ipAddresses"
tlsCertificateIpAddresses = AttrLabelProxy

tlsCertificateIssuer :: AttrLabelProxy "issuer"
tlsCertificateIssuer = AttrLabelProxy

tlsCertificateIssuerName :: AttrLabelProxy "issuerName"
tlsCertificateIssuerName = AttrLabelProxy

tlsCertificateNotValidAfter :: AttrLabelProxy "notValidAfter"
tlsCertificateNotValidAfter = AttrLabelProxy

tlsCertificateNotValidBefore :: AttrLabelProxy "notValidBefore"
tlsCertificateNotValidBefore = AttrLabelProxy

tlsCertificatePkcs11Uri :: AttrLabelProxy "pkcs11Uri"
tlsCertificatePkcs11Uri = AttrLabelProxy

tlsCertificatePrivateKey :: AttrLabelProxy "privateKey"
tlsCertificatePrivateKey = AttrLabelProxy

tlsCertificatePrivateKeyPem :: AttrLabelProxy "privateKeyPem"
tlsCertificatePrivateKeyPem = AttrLabelProxy

tlsCertificatePrivateKeyPkcs11Uri :: AttrLabelProxy "privateKeyPkcs11Uri"
tlsCertificatePrivateKeyPkcs11Uri = AttrLabelProxy

tlsCertificateSubjectName :: AttrLabelProxy "subjectName"
tlsCertificateSubjectName = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TlsCertificate = TlsCertificateSignalList
type TlsCertificateSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method TlsCertificate::new_from_file
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "file"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "file containing a PEM-encoded certificate to import"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "TlsCertificate" })
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_certificate_new_from_file" g_tls_certificate_new_from_file :: 
    CString ->                              -- file : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr TlsCertificate)

-- | Creates a t'GI.Gio.Objects.TlsCertificate.TlsCertificate' from the PEM-encoded data in /@file@/. The
-- returned certificate will be the first certificate found in /@file@/. As
-- of GLib 2.44, if /@file@/ contains more certificates it will try to load
-- a certificate chain. All certificates will be verified in the order
-- found (top-level certificate should be the last one in the file) and
-- the [TlsCertificate:issuer]("GI.Gio.Objects.TlsCertificate#g:attr:issuer") property of each certificate will be set
-- accordingly if the verification succeeds. If any certificate in the
-- chain cannot be verified, the first certificate in the file will
-- still be returned.
-- 
-- If /@file@/ cannot be read or parsed, the function will return 'P.Nothing' and
-- set /@error@/. Otherwise, this behaves like
-- 'GI.Gio.Objects.TlsCertificate.tlsCertificateNewFromPem'.
-- 
-- /Since: 2.28/
tlsCertificateNewFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@file@/: file containing a PEM-encoded certificate to import
    -> m TlsCertificate
    -- ^ __Returns:__ the new certificate, or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
tlsCertificateNewFromFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m TlsCertificate
tlsCertificateNewFromFile String
file = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsCertificate -> m TlsCertificate)
-> IO TlsCertificate -> m TlsCertificate
forall a b. (a -> b) -> a -> b
$ do
    CString
file' <- String -> IO CString
stringToCString String
file
    IO TlsCertificate -> IO () -> IO TlsCertificate
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr TlsCertificate
result <- (Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
-> IO (Ptr TlsCertificate)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
 -> IO (Ptr TlsCertificate))
-> (Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
-> IO (Ptr TlsCertificate)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr TlsCertificate)
g_tls_certificate_new_from_file CString
file'
        Text -> Ptr TlsCertificate -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsCertificateNewFromFile" Ptr TlsCertificate
result
        TlsCertificate
result' <- ((ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate) Ptr TlsCertificate
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method TlsCertificate::new_from_files
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "cert_file"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "file containing one or more PEM-encoded\n    certificates to import"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key_file"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "file containing a PEM-encoded private key\n    to import"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "TlsCertificate" })
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_certificate_new_from_files" g_tls_certificate_new_from_files :: 
    CString ->                              -- cert_file : TBasicType TFileName
    CString ->                              -- key_file : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr TlsCertificate)

-- | Creates a t'GI.Gio.Objects.TlsCertificate.TlsCertificate' from the PEM-encoded data in /@certFile@/
-- and /@keyFile@/. The returned certificate will be the first certificate
-- found in /@certFile@/. As of GLib 2.44, if /@certFile@/ contains more
-- certificates it will try to load a certificate chain. All
-- certificates will be verified in the order found (top-level
-- certificate should be the last one in the file) and the
-- [TlsCertificate:issuer]("GI.Gio.Objects.TlsCertificate#g:attr:issuer") property of each certificate will be set
-- accordingly if the verification succeeds. If any certificate in the
-- chain cannot be verified, the first certificate in the file will
-- still be returned.
-- 
-- If either file cannot be read or parsed, the function will return
-- 'P.Nothing' and set /@error@/. Otherwise, this behaves like
-- 'GI.Gio.Objects.TlsCertificate.tlsCertificateNewFromPem'.
-- 
-- /Since: 2.28/
tlsCertificateNewFromFiles ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@certFile@/: file containing one or more PEM-encoded
    --     certificates to import
    -> [Char]
    -- ^ /@keyFile@/: file containing a PEM-encoded private key
    --     to import
    -> m TlsCertificate
    -- ^ __Returns:__ the new certificate, or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
tlsCertificateNewFromFiles :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> String -> m TlsCertificate
tlsCertificateNewFromFiles String
certFile String
keyFile = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsCertificate -> m TlsCertificate)
-> IO TlsCertificate -> m TlsCertificate
forall a b. (a -> b) -> a -> b
$ do
    CString
certFile' <- String -> IO CString
stringToCString String
certFile
    CString
keyFile' <- String -> IO CString
stringToCString String
keyFile
    IO TlsCertificate -> IO () -> IO TlsCertificate
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr TlsCertificate
result <- (Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
-> IO (Ptr TlsCertificate)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
 -> IO (Ptr TlsCertificate))
-> (Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
-> IO (Ptr TlsCertificate)
forall a b. (a -> b) -> a -> b
$ CString -> CString -> Ptr (Ptr GError) -> IO (Ptr TlsCertificate)
g_tls_certificate_new_from_files CString
certFile' CString
keyFile'
        Text -> Ptr TlsCertificate -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsCertificateNewFromFiles" Ptr TlsCertificate
result
        TlsCertificate
result' <- ((ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate) Ptr TlsCertificate
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
certFile'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
keyFile'
        TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
certFile'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
keyFile'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method TlsCertificate::new_from_pem
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "data"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "PEM-encoded certificate data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the length of @data, or -1 if it's 0-terminated."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "TlsCertificate" })
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_certificate_new_from_pem" g_tls_certificate_new_from_pem :: 
    CString ->                              -- data : TBasicType TUTF8
    Int64 ->                                -- length : TBasicType TInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr TlsCertificate)

-- | Creates a t'GI.Gio.Objects.TlsCertificate.TlsCertificate' from the PEM-encoded data in /@data@/. If
-- /@data@/ includes both a certificate and a private key, then the
-- returned certificate will include the private key data as well. (See
-- the [TlsCertificate:privateKeyPem]("GI.Gio.Objects.TlsCertificate#g:attr:privateKeyPem") property for information about
-- supported formats.)
-- 
-- The returned certificate will be the first certificate found in
-- /@data@/. As of GLib 2.44, if /@data@/ contains more certificates it will
-- try to load a certificate chain. All certificates will be verified in
-- the order found (top-level certificate should be the last one in the
-- file) and the [TlsCertificate:issuer]("GI.Gio.Objects.TlsCertificate#g:attr:issuer") property of each certificate
-- will be set accordingly if the verification succeeds. If any
-- certificate in the chain cannot be verified, the first certificate in
-- the file will still be returned.
-- 
-- /Since: 2.28/
tlsCertificateNewFromPem ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@data@/: PEM-encoded certificate data
    -> Int64
    -- ^ /@length@/: the length of /@data@/, or -1 if it\'s 0-terminated.
    -> m TlsCertificate
    -- ^ __Returns:__ the new certificate, or 'P.Nothing' if /@data@/ is invalid /(Can throw 'Data.GI.Base.GError.GError')/
tlsCertificateNewFromPem :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Int64 -> m TlsCertificate
tlsCertificateNewFromPem Text
data_ Int64
length_ = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsCertificate -> m TlsCertificate)
-> IO TlsCertificate -> m TlsCertificate
forall a b. (a -> b) -> a -> b
$ do
    CString
data_' <- Text -> IO CString
textToCString Text
data_
    IO TlsCertificate -> IO () -> IO TlsCertificate
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr TlsCertificate
result <- (Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
-> IO (Ptr TlsCertificate)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
 -> IO (Ptr TlsCertificate))
-> (Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
-> IO (Ptr TlsCertificate)
forall a b. (a -> b) -> a -> b
$ CString -> Int64 -> Ptr (Ptr GError) -> IO (Ptr TlsCertificate)
g_tls_certificate_new_from_pem CString
data_' Int64
length_
        Text -> Ptr TlsCertificate -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsCertificateNewFromPem" Ptr TlsCertificate
result
        TlsCertificate
result' <- ((ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate) Ptr TlsCertificate
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
data_'
        TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
data_'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method TlsCertificate::new_from_pkcs11_uris
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "pkcs11_uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A PKCS \\#11 URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "private_key_pkcs11_uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A PKCS \\#11 URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "TlsCertificate" })
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_certificate_new_from_pkcs11_uris" g_tls_certificate_new_from_pkcs11_uris :: 
    CString ->                              -- pkcs11_uri : TBasicType TUTF8
    CString ->                              -- private_key_pkcs11_uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr TlsCertificate)

-- | Creates a t'GI.Gio.Objects.TlsCertificate.TlsCertificate' from a
-- <https://docs.oasis-open.org/pkcs11/pkcs11-base/v3.0/os/pkcs11-base-v3.0-os.html PKCS \#11> URI.
-- 
-- An example /@pkcs11Uri@/ would be @pkcs11:model=Model;manufacturer=Manufacture;serial=1;token=My%20Client%20Certificate;id=%01@
-- 
-- Where the token’s layout is:
-- 
-- >
-- >Object 0:
-- >  URL: pkcs11:model=Model;manufacturer=Manufacture;serial=1;token=My%20Client%20Certificate;id=%01;object=private%20key;type=private
-- >  Type: Private key (RSA-2048)
-- >  ID: 01
-- >
-- >Object 1:
-- >  URL: pkcs11:model=Model;manufacturer=Manufacture;serial=1;token=My%20Client%20Certificate;id=%01;object=Certificate%20for%20Authentication;type=cert
-- >  Type: X.509 Certificate (RSA-2048)
-- >  ID: 01
-- 
-- 
-- In this case the certificate and private key would both be detected and used as expected.
-- /@pkcsUri@/ may also just reference an X.509 certificate object and then optionally
-- /@privateKeyPkcs11Uri@/ allows using a private key exposed under a different URI.
-- 
-- Note that the private key is not accessed until usage and may fail or require a PIN later.
-- 
-- /Since: 2.68/
tlsCertificateNewFromPkcs11Uris ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@pkcs11Uri@/: A PKCS #11 URI
    -> Maybe (T.Text)
    -- ^ /@privateKeyPkcs11Uri@/: A PKCS #11 URI
    -> m TlsCertificate
    -- ^ __Returns:__ the new certificate, or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
tlsCertificateNewFromPkcs11Uris :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Maybe Text -> m TlsCertificate
tlsCertificateNewFromPkcs11Uris Text
pkcs11Uri Maybe Text
privateKeyPkcs11Uri = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsCertificate -> m TlsCertificate)
-> IO TlsCertificate -> m TlsCertificate
forall a b. (a -> b) -> a -> b
$ do
    CString
pkcs11Uri' <- Text -> IO CString
textToCString Text
pkcs11Uri
    CString
maybePrivateKeyPkcs11Uri <- case Maybe Text
privateKeyPkcs11Uri of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jPrivateKeyPkcs11Uri -> do
            CString
jPrivateKeyPkcs11Uri' <- Text -> IO CString
textToCString Text
jPrivateKeyPkcs11Uri
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jPrivateKeyPkcs11Uri'
    IO TlsCertificate -> IO () -> IO TlsCertificate
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr TlsCertificate
result <- (Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
-> IO (Ptr TlsCertificate)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
 -> IO (Ptr TlsCertificate))
-> (Ptr (Ptr GError) -> IO (Ptr TlsCertificate))
-> IO (Ptr TlsCertificate)
forall a b. (a -> b) -> a -> b
$ CString -> CString -> Ptr (Ptr GError) -> IO (Ptr TlsCertificate)
g_tls_certificate_new_from_pkcs11_uris CString
pkcs11Uri' CString
maybePrivateKeyPkcs11Uri
        Text -> Ptr TlsCertificate -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsCertificateNewFromPkcs11Uris" Ptr TlsCertificate
result
        TlsCertificate
result' <- ((ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate) Ptr TlsCertificate
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
pkcs11Uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePrivateKeyPkcs11Uri
        TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
pkcs11Uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePrivateKeyPkcs11Uri
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method TlsCertificate::get_dns_names
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cert"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsCertificate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TPtrArray
--                  (TInterface Name { namespace = "GLib" , name = "Bytes" }))
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_certificate_get_dns_names" g_tls_certificate_get_dns_names :: 
    Ptr TlsCertificate ->                   -- cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO (Ptr (GPtrArray (Ptr GLib.Bytes.Bytes)))

-- | Gets the value of [TlsCertificate:dnsNames]("GI.Gio.Objects.TlsCertificate#g:attr:dnsNames").
-- 
-- /Since: 2.70/
tlsCertificateGetDnsNames ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a) =>
    a
    -- ^ /@cert@/: a t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> m (Maybe [GLib.Bytes.Bytes])
    -- ^ __Returns:__ A t'GI.GLib.Structs.PtrArray.PtrArray' of
    -- t'GI.GLib.Structs.Bytes.Bytes' elements, or 'P.Nothing' if it\'s not available.
tlsCertificateGetDnsNames :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsCertificate a) =>
a -> m (Maybe [Bytes])
tlsCertificateGetDnsNames a
cert = IO (Maybe [Bytes]) -> m (Maybe [Bytes])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Bytes]) -> m (Maybe [Bytes]))
-> IO (Maybe [Bytes]) -> m (Maybe [Bytes])
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsCertificate
cert' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cert
    Ptr (GPtrArray (Ptr Bytes))
result <- Ptr TlsCertificate -> IO (Ptr (GPtrArray (Ptr Bytes)))
g_tls_certificate_get_dns_names Ptr TlsCertificate
cert'
    Maybe [Bytes]
maybeResult <- Ptr (GPtrArray (Ptr Bytes))
-> (Ptr (GPtrArray (Ptr Bytes)) -> IO [Bytes])
-> IO (Maybe [Bytes])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr (GPtrArray (Ptr Bytes))
result ((Ptr (GPtrArray (Ptr Bytes)) -> IO [Bytes]) -> IO (Maybe [Bytes]))
-> (Ptr (GPtrArray (Ptr Bytes)) -> IO [Bytes])
-> IO (Maybe [Bytes])
forall a b. (a -> b) -> a -> b
$ \Ptr (GPtrArray (Ptr Bytes))
result' -> do
        [Ptr Bytes]
result'' <- Ptr (GPtrArray (Ptr Bytes)) -> IO [Ptr Bytes]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr Bytes))
result'
        [Bytes]
result''' <- (Ptr Bytes -> IO Bytes) -> [Ptr Bytes] -> IO [Bytes]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) [Ptr Bytes]
result''
        Ptr (GPtrArray (Ptr Bytes)) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray (Ptr Bytes))
result'
        [Bytes] -> IO [Bytes]
forall (m :: * -> *) a. Monad m => a -> m a
return [Bytes]
result'''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cert
    Maybe [Bytes] -> IO (Maybe [Bytes])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Bytes]
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsCertificateGetDnsNamesMethodInfo
instance (signature ~ (m (Maybe [GLib.Bytes.Bytes])), MonadIO m, IsTlsCertificate a) => O.OverloadedMethod TlsCertificateGetDnsNamesMethodInfo a signature where
    overloadedMethod = tlsCertificateGetDnsNames

instance O.OverloadedMethodInfo TlsCertificateGetDnsNamesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateGetDnsNames",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateGetDnsNames"
        })


#endif

-- method TlsCertificate::get_ip_addresses
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cert"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsCertificate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TPtrArray
--                  (TInterface Name { namespace = "Gio" , name = "InetAddress" }))
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_certificate_get_ip_addresses" g_tls_certificate_get_ip_addresses :: 
    Ptr TlsCertificate ->                   -- cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO (Ptr (GPtrArray (Ptr Gio.InetAddress.InetAddress)))

-- | Gets the value of [TlsCertificate:ipAddresses]("GI.Gio.Objects.TlsCertificate#g:attr:ipAddresses").
-- 
-- /Since: 2.70/
tlsCertificateGetIpAddresses ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a) =>
    a
    -- ^ /@cert@/: a t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> m (Maybe [Gio.InetAddress.InetAddress])
    -- ^ __Returns:__ A t'GI.GLib.Structs.PtrArray.PtrArray'
    -- of t'GI.Gio.Objects.InetAddress.InetAddress' elements, or 'P.Nothing' if it\'s not available.
tlsCertificateGetIpAddresses :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsCertificate a) =>
a -> m (Maybe [InetAddress])
tlsCertificateGetIpAddresses a
cert = IO (Maybe [InetAddress]) -> m (Maybe [InetAddress])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [InetAddress]) -> m (Maybe [InetAddress]))
-> IO (Maybe [InetAddress]) -> m (Maybe [InetAddress])
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsCertificate
cert' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cert
    Ptr (GPtrArray (Ptr InetAddress))
result <- Ptr TlsCertificate -> IO (Ptr (GPtrArray (Ptr InetAddress)))
g_tls_certificate_get_ip_addresses Ptr TlsCertificate
cert'
    Maybe [InetAddress]
maybeResult <- Ptr (GPtrArray (Ptr InetAddress))
-> (Ptr (GPtrArray (Ptr InetAddress)) -> IO [InetAddress])
-> IO (Maybe [InetAddress])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr (GPtrArray (Ptr InetAddress))
result ((Ptr (GPtrArray (Ptr InetAddress)) -> IO [InetAddress])
 -> IO (Maybe [InetAddress]))
-> (Ptr (GPtrArray (Ptr InetAddress)) -> IO [InetAddress])
-> IO (Maybe [InetAddress])
forall a b. (a -> b) -> a -> b
$ \Ptr (GPtrArray (Ptr InetAddress))
result' -> do
        [Ptr InetAddress]
result'' <- Ptr (GPtrArray (Ptr InetAddress)) -> IO [Ptr InetAddress]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr InetAddress))
result'
        [InetAddress]
result''' <- (Ptr InetAddress -> IO InetAddress)
-> [Ptr InetAddress] -> IO [InetAddress]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr InetAddress -> InetAddress)
-> Ptr InetAddress -> IO InetAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InetAddress -> InetAddress
Gio.InetAddress.InetAddress) [Ptr InetAddress]
result''
        Ptr (GPtrArray (Ptr InetAddress)) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray (Ptr InetAddress))
result'
        [InetAddress] -> IO [InetAddress]
forall (m :: * -> *) a. Monad m => a -> m a
return [InetAddress]
result'''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cert
    Maybe [InetAddress] -> IO (Maybe [InetAddress])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [InetAddress]
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsCertificateGetIpAddressesMethodInfo
instance (signature ~ (m (Maybe [Gio.InetAddress.InetAddress])), MonadIO m, IsTlsCertificate a) => O.OverloadedMethod TlsCertificateGetIpAddressesMethodInfo a signature where
    overloadedMethod = tlsCertificateGetIpAddresses

instance O.OverloadedMethodInfo TlsCertificateGetIpAddressesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateGetIpAddresses",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateGetIpAddresses"
        })


#endif

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

foreign import ccall "g_tls_certificate_get_issuer" g_tls_certificate_get_issuer :: 
    Ptr TlsCertificate ->                   -- cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO (Ptr TlsCertificate)

-- | Gets the t'GI.Gio.Objects.TlsCertificate.TlsCertificate' representing /@cert@/\'s issuer, if known
-- 
-- /Since: 2.28/
tlsCertificateGetIssuer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a) =>
    a
    -- ^ /@cert@/: a t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> m (Maybe TlsCertificate)
    -- ^ __Returns:__ The certificate of /@cert@/\'s issuer,
    -- or 'P.Nothing' if /@cert@/ is self-signed or signed with an unknown
    -- certificate.
tlsCertificateGetIssuer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsCertificate a) =>
a -> m (Maybe TlsCertificate)
tlsCertificateGetIssuer a
cert = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
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
    Ptr TlsCertificate
cert' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cert
    Ptr TlsCertificate
result <- Ptr TlsCertificate -> IO (Ptr TlsCertificate)
g_tls_certificate_get_issuer Ptr TlsCertificate
cert'
    Maybe TlsCertificate
maybeResult <- Ptr TlsCertificate
-> (Ptr TlsCertificate -> IO TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TlsCertificate
result ((Ptr TlsCertificate -> IO TlsCertificate)
 -> IO (Maybe TlsCertificate))
-> (Ptr TlsCertificate -> IO TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b. (a -> b) -> a -> b
$ \Ptr TlsCertificate
result' -> do
        TlsCertificate
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
TlsCertificate) Ptr TlsCertificate
result'
        TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cert
    Maybe TlsCertificate -> IO (Maybe TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsCertificate
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsCertificateGetIssuerMethodInfo
instance (signature ~ (m (Maybe TlsCertificate)), MonadIO m, IsTlsCertificate a) => O.OverloadedMethod TlsCertificateGetIssuerMethodInfo a signature where
    overloadedMethod = tlsCertificateGetIssuer

instance O.OverloadedMethodInfo TlsCertificateGetIssuerMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateGetIssuer",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateGetIssuer"
        })


#endif

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

foreign import ccall "g_tls_certificate_get_issuer_name" g_tls_certificate_get_issuer_name :: 
    Ptr TlsCertificate ->                   -- cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO CString

-- | Returns the issuer name from the certificate.
-- 
-- /Since: 2.70/
tlsCertificateGetIssuerName ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a) =>
    a
    -- ^ /@cert@/: a t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The issuer name, or 'P.Nothing' if it\'s not available.
tlsCertificateGetIssuerName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsCertificate a) =>
a -> m (Maybe Text)
tlsCertificateGetIssuerName a
cert = IO (Maybe Text) -> m (Maybe Text)
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
    Ptr TlsCertificate
cert' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cert
    CString
result <- Ptr TlsCertificate -> IO CString
g_tls_certificate_get_issuer_name Ptr TlsCertificate
cert'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cert
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsCertificateGetIssuerNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsTlsCertificate a) => O.OverloadedMethod TlsCertificateGetIssuerNameMethodInfo a signature where
    overloadedMethod = tlsCertificateGetIssuerName

instance O.OverloadedMethodInfo TlsCertificateGetIssuerNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateGetIssuerName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateGetIssuerName"
        })


#endif

-- method TlsCertificate::get_not_valid_after
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cert"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsCertificate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "DateTime" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_certificate_get_not_valid_after" g_tls_certificate_get_not_valid_after :: 
    Ptr TlsCertificate ->                   -- cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO (Ptr GLib.DateTime.DateTime)

-- | Returns the time at which the certificate became or will become invalid.
-- 
-- /Since: 2.70/
tlsCertificateGetNotValidAfter ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a) =>
    a
    -- ^ /@cert@/: a t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> m (Maybe GLib.DateTime.DateTime)
    -- ^ __Returns:__ The not-valid-after date, or 'P.Nothing' if it\'s not available.
tlsCertificateGetNotValidAfter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsCertificate a) =>
a -> m (Maybe DateTime)
tlsCertificateGetNotValidAfter a
cert = IO (Maybe DateTime) -> m (Maybe DateTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DateTime) -> m (Maybe DateTime))
-> IO (Maybe DateTime) -> m (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsCertificate
cert' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cert
    Ptr DateTime
result <- Ptr TlsCertificate -> IO (Ptr DateTime)
g_tls_certificate_get_not_valid_after Ptr TlsCertificate
cert'
    Maybe DateTime
maybeResult <- Ptr DateTime
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DateTime
result ((Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime))
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ \Ptr DateTime
result' -> do
        DateTime
result'' <- ((ManagedPtr DateTime -> DateTime) -> Ptr DateTime -> IO DateTime
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime) Ptr DateTime
result'
        DateTime -> IO DateTime
forall (m :: * -> *) a. Monad m => a -> m a
return DateTime
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cert
    Maybe DateTime -> IO (Maybe DateTime)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DateTime
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsCertificateGetNotValidAfterMethodInfo
instance (signature ~ (m (Maybe GLib.DateTime.DateTime)), MonadIO m, IsTlsCertificate a) => O.OverloadedMethod TlsCertificateGetNotValidAfterMethodInfo a signature where
    overloadedMethod = tlsCertificateGetNotValidAfter

instance O.OverloadedMethodInfo TlsCertificateGetNotValidAfterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateGetNotValidAfter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateGetNotValidAfter"
        })


#endif

-- method TlsCertificate::get_not_valid_before
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cert"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsCertificate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "DateTime" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_certificate_get_not_valid_before" g_tls_certificate_get_not_valid_before :: 
    Ptr TlsCertificate ->                   -- cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO (Ptr GLib.DateTime.DateTime)

-- | Returns the time at which the certificate became or will become valid.
-- 
-- /Since: 2.70/
tlsCertificateGetNotValidBefore ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a) =>
    a
    -- ^ /@cert@/: a t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> m (Maybe GLib.DateTime.DateTime)
    -- ^ __Returns:__ The not-valid-before date, or 'P.Nothing' if it\'s not available.
tlsCertificateGetNotValidBefore :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsCertificate a) =>
a -> m (Maybe DateTime)
tlsCertificateGetNotValidBefore a
cert = IO (Maybe DateTime) -> m (Maybe DateTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DateTime) -> m (Maybe DateTime))
-> IO (Maybe DateTime) -> m (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TlsCertificate
cert' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cert
    Ptr DateTime
result <- Ptr TlsCertificate -> IO (Ptr DateTime)
g_tls_certificate_get_not_valid_before Ptr TlsCertificate
cert'
    Maybe DateTime
maybeResult <- Ptr DateTime
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DateTime
result ((Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime))
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ \Ptr DateTime
result' -> do
        DateTime
result'' <- ((ManagedPtr DateTime -> DateTime) -> Ptr DateTime -> IO DateTime
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime) Ptr DateTime
result'
        DateTime -> IO DateTime
forall (m :: * -> *) a. Monad m => a -> m a
return DateTime
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cert
    Maybe DateTime -> IO (Maybe DateTime)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DateTime
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsCertificateGetNotValidBeforeMethodInfo
instance (signature ~ (m (Maybe GLib.DateTime.DateTime)), MonadIO m, IsTlsCertificate a) => O.OverloadedMethod TlsCertificateGetNotValidBeforeMethodInfo a signature where
    overloadedMethod = tlsCertificateGetNotValidBefore

instance O.OverloadedMethodInfo TlsCertificateGetNotValidBeforeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateGetNotValidBefore",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateGetNotValidBefore"
        })


#endif

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

foreign import ccall "g_tls_certificate_get_subject_name" g_tls_certificate_get_subject_name :: 
    Ptr TlsCertificate ->                   -- cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO CString

-- | Returns the subject name from the certificate.
-- 
-- /Since: 2.70/
tlsCertificateGetSubjectName ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a) =>
    a
    -- ^ /@cert@/: a t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The subject name, or 'P.Nothing' if it\'s not available.
tlsCertificateGetSubjectName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsCertificate a) =>
a -> m (Maybe Text)
tlsCertificateGetSubjectName a
cert = IO (Maybe Text) -> m (Maybe Text)
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
    Ptr TlsCertificate
cert' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cert
    CString
result <- Ptr TlsCertificate -> IO CString
g_tls_certificate_get_subject_name Ptr TlsCertificate
cert'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cert
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data TlsCertificateGetSubjectNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsTlsCertificate a) => O.OverloadedMethod TlsCertificateGetSubjectNameMethodInfo a signature where
    overloadedMethod = tlsCertificateGetSubjectName

instance O.OverloadedMethodInfo TlsCertificateGetSubjectNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateGetSubjectName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateGetSubjectName"
        })


#endif

-- method TlsCertificate::is_same
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cert_one"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first certificate to compare"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cert_two"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "second certificate to compare"
--                 , 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_certificate_is_same" g_tls_certificate_is_same :: 
    Ptr TlsCertificate ->                   -- cert_one : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    Ptr TlsCertificate ->                   -- cert_two : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO CInt

-- | Check if two t'GI.Gio.Objects.TlsCertificate.TlsCertificate' objects represent the same certificate.
-- The raw DER byte data of the two certificates are checked for equality.
-- This has the effect that two certificates may compare equal even if
-- their [TlsCertificate:issuer]("GI.Gio.Objects.TlsCertificate#g:attr:issuer"), [TlsCertificate:privateKey]("GI.Gio.Objects.TlsCertificate#g:attr:privateKey"), or
-- [TlsCertificate:privateKeyPem]("GI.Gio.Objects.TlsCertificate#g:attr:privateKeyPem") properties differ.
-- 
-- /Since: 2.34/
tlsCertificateIsSame ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a, IsTlsCertificate b) =>
    a
    -- ^ /@certOne@/: first certificate to compare
    -> b
    -- ^ /@certTwo@/: second certificate to compare
    -> m Bool
    -- ^ __Returns:__ whether the same or not
tlsCertificateIsSame :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTlsCertificate a,
 IsTlsCertificate b) =>
a -> b -> m Bool
tlsCertificateIsSame a
certOne b
certTwo = 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 TlsCertificate
certOne' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
certOne
    Ptr TlsCertificate
certTwo' <- b -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
certTwo
    CInt
result <- Ptr TlsCertificate -> Ptr TlsCertificate -> IO CInt
g_tls_certificate_is_same Ptr TlsCertificate
certOne' Ptr TlsCertificate
certTwo'
    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
certOne
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
certTwo
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TlsCertificateIsSameMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsTlsCertificate a, IsTlsCertificate b) => O.OverloadedMethod TlsCertificateIsSameMethodInfo a signature where
    overloadedMethod = tlsCertificateIsSame

instance O.OverloadedMethodInfo TlsCertificateIsSameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateIsSame",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateIsSame"
        })


#endif

-- method TlsCertificate::verify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cert"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsCertificate" , 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 = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the expected peer identity"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "trusted_ca"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsCertificate" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the certificate of a trusted authority"
--                 , 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_certificate_verify" g_tls_certificate_verify :: 
    Ptr TlsCertificate ->                   -- cert : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    Ptr Gio.SocketConnectable.SocketConnectable -> -- identity : TInterface (Name {namespace = "Gio", name = "SocketConnectable"})
    Ptr TlsCertificate ->                   -- trusted_ca : TInterface (Name {namespace = "Gio", name = "TlsCertificate"})
    IO CUInt

-- | This verifies /@cert@/ and returns a set of t'GI.Gio.Flags.TlsCertificateFlags'
-- indicating any problems found with it. This can be used to verify a
-- certificate outside the context of making a connection, or to
-- check a certificate against a CA that is not part of the system
-- CA database.
-- 
-- If /@identity@/ is not 'P.Nothing', /@cert@/\'s name(s) will be compared against
-- it, and 'GI.Gio.Flags.TlsCertificateFlagsBadIdentity' will be set in the return
-- value if it does not match. If /@identity@/ is 'P.Nothing', that bit will
-- never be set in the return value.
-- 
-- If /@trustedCa@/ is not 'P.Nothing', then /@cert@/ (or one of the certificates
-- in its chain) must be signed by it, or else
-- 'GI.Gio.Flags.TlsCertificateFlagsUnknownCa' will be set in the return value. If
-- /@trustedCa@/ is 'P.Nothing', that bit will never be set in the return
-- value.
-- 
-- (All other t'GI.Gio.Flags.TlsCertificateFlags' values will always be set or unset
-- as appropriate.)
-- 
-- Because TLS session context is not used, t'GI.Gio.Objects.TlsCertificate.TlsCertificate' may not
-- perform as many checks on the certificates as t'GI.Gio.Objects.TlsConnection.TlsConnection' would.
-- For example, certificate constraints cannot be honored, and some
-- revocation checks cannot be performed. The best way to verify TLS
-- certificates used by a TLS connection is to let t'GI.Gio.Objects.TlsConnection.TlsConnection'
-- handle the verification.
-- 
-- /Since: 2.28/
tlsCertificateVerify ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a, Gio.SocketConnectable.IsSocketConnectable b, IsTlsCertificate c) =>
    a
    -- ^ /@cert@/: a t'GI.Gio.Objects.TlsCertificate.TlsCertificate'
    -> Maybe (b)
    -- ^ /@identity@/: the expected peer identity
    -> Maybe (c)
    -- ^ /@trustedCa@/: the certificate of a trusted authority
    -> m [Gio.Flags.TlsCertificateFlags]
    -- ^ __Returns:__ the appropriate t'GI.Gio.Flags.TlsCertificateFlags'
tlsCertificateVerify :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsTlsCertificate a,
 IsSocketConnectable b, IsTlsCertificate c) =>
a -> Maybe b -> Maybe c -> m [TlsCertificateFlags]
tlsCertificateVerify a
cert Maybe b
identity Maybe c
trustedCa = 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 TlsCertificate
cert' <- a -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cert
    Ptr SocketConnectable
maybeIdentity <- case Maybe b
identity 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
jIdentity -> do
            Ptr SocketConnectable
jIdentity' <- b -> IO (Ptr SocketConnectable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jIdentity
            Ptr SocketConnectable -> IO (Ptr SocketConnectable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketConnectable
jIdentity'
    Ptr TlsCertificate
maybeTrustedCa <- case Maybe c
trustedCa of
        Maybe c
Nothing -> Ptr TlsCertificate -> IO (Ptr TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsCertificate
forall a. Ptr a
nullPtr
        Just c
jTrustedCa -> do
            Ptr TlsCertificate
jTrustedCa' <- c -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jTrustedCa
            Ptr TlsCertificate -> IO (Ptr TlsCertificate)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TlsCertificate
jTrustedCa'
    CUInt
result <- Ptr TlsCertificate
-> Ptr SocketConnectable -> Ptr TlsCertificate -> IO CUInt
g_tls_certificate_verify Ptr TlsCertificate
cert' Ptr SocketConnectable
maybeIdentity Ptr TlsCertificate
maybeTrustedCa
    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
cert
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
identity b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
trustedCa c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    [TlsCertificateFlags] -> IO [TlsCertificateFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [TlsCertificateFlags]
result'

#if defined(ENABLE_OVERLOADING)
data TlsCertificateVerifyMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (c) -> m [Gio.Flags.TlsCertificateFlags]), MonadIO m, IsTlsCertificate a, Gio.SocketConnectable.IsSocketConnectable b, IsTlsCertificate c) => O.OverloadedMethod TlsCertificateVerifyMethodInfo a signature where
    overloadedMethod = tlsCertificateVerify

instance O.OverloadedMethodInfo TlsCertificateVerifyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsCertificate.tlsCertificateVerify",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-TlsCertificate.html#v:tlsCertificateVerify"
        })


#endif

-- method TlsCertificate::list_new_from_file
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "file"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "file containing PEM-encoded certificates to import"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "Gio" , name = "TlsCertificate" }))
-- throws : True
-- Skip return : False

foreign import ccall "g_tls_certificate_list_new_from_file" g_tls_certificate_list_new_from_file :: 
    CString ->                              -- file : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr (GList (Ptr TlsCertificate)))

-- | Creates one or more @/GTlsCertificates/@ from the PEM-encoded
-- data in /@file@/. If /@file@/ cannot be read or parsed, the function will
-- return 'P.Nothing' and set /@error@/. If /@file@/ does not contain any
-- PEM-encoded certificates, this will return an empty list and not
-- set /@error@/.
-- 
-- /Since: 2.28/
tlsCertificateListNewFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@file@/: file containing PEM-encoded certificates to import
    -> m [TlsCertificate]
    -- ^ __Returns:__ a
    -- t'GI.GLib.Structs.List.List' containing t'GI.Gio.Objects.TlsCertificate.TlsCertificate' objects. You must free the list
    -- and its contents when you are done with it. /(Can throw 'Data.GI.Base.GError.GError')/
tlsCertificateListNewFromFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m [TlsCertificate]
tlsCertificateListNewFromFile String
file = IO [TlsCertificate] -> m [TlsCertificate]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TlsCertificate] -> m [TlsCertificate])
-> IO [TlsCertificate] -> m [TlsCertificate]
forall a b. (a -> b) -> a -> b
$ do
    CString
file' <- String -> IO CString
stringToCString String
file
    IO [TlsCertificate] -> IO () -> IO [TlsCertificate]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr (GList (Ptr TlsCertificate))
result <- (Ptr (Ptr GError) -> IO (Ptr (GList (Ptr TlsCertificate))))
-> IO (Ptr (GList (Ptr TlsCertificate)))
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr (GList (Ptr TlsCertificate))))
 -> IO (Ptr (GList (Ptr TlsCertificate))))
-> (Ptr (Ptr GError) -> IO (Ptr (GList (Ptr TlsCertificate))))
-> IO (Ptr (GList (Ptr TlsCertificate)))
forall a b. (a -> b) -> a -> b
$ CString
-> Ptr (Ptr GError) -> IO (Ptr (GList (Ptr TlsCertificate)))
g_tls_certificate_list_new_from_file CString
file'
        [Ptr TlsCertificate]
result' <- Ptr (GList (Ptr TlsCertificate)) -> IO [Ptr TlsCertificate]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr TlsCertificate))
result
        [TlsCertificate]
result'' <- (Ptr TlsCertificate -> IO TlsCertificate)
-> [Ptr TlsCertificate] -> IO [TlsCertificate]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr TlsCertificate -> TlsCertificate)
-> Ptr TlsCertificate -> IO TlsCertificate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate) [Ptr TlsCertificate]
result'
        Ptr (GList (Ptr TlsCertificate)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr TlsCertificate))
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        [TlsCertificate] -> IO [TlsCertificate]
forall (m :: * -> *) a. Monad m => a -> m a
return [TlsCertificate]
result''
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
     )

#if defined(ENABLE_OVERLOADING)
#endif