{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.TlsCertificate
(
TlsCertificate(..) ,
IsTlsCertificate ,
toTlsCertificate ,
#if defined(ENABLE_OVERLOADING)
ResolveTlsCertificateMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsCertificateGetIssuerMethodInfo ,
#endif
tlsCertificateGetIssuer ,
#if defined(ENABLE_OVERLOADING)
TlsCertificateIsSameMethodInfo ,
#endif
tlsCertificateIsSame ,
tlsCertificateListNewFromFile ,
tlsCertificateNewFromFile ,
tlsCertificateNewFromFiles ,
tlsCertificateNewFromPem ,
#if defined(ENABLE_OVERLOADING)
TlsCertificateVerifyMethodInfo ,
#endif
tlsCertificateVerify ,
#if defined(ENABLE_OVERLOADING)
TlsCertificateCertificatePropertyInfo ,
#endif
constructTlsCertificateCertificate ,
getTlsCertificateCertificate ,
#if defined(ENABLE_OVERLOADING)
tlsCertificateCertificate ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsCertificateCertificatePemPropertyInfo,
#endif
constructTlsCertificateCertificatePem ,
getTlsCertificateCertificatePem ,
#if defined(ENABLE_OVERLOADING)
tlsCertificateCertificatePem ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsCertificateIssuerPropertyInfo ,
#endif
constructTlsCertificateIssuer ,
getTlsCertificateIssuer ,
#if defined(ENABLE_OVERLOADING)
tlsCertificateIssuer ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsCertificatePrivateKeyPropertyInfo ,
#endif
constructTlsCertificatePrivateKey ,
#if defined(ENABLE_OVERLOADING)
tlsCertificatePrivateKey ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsCertificatePrivateKeyPemPropertyInfo ,
#endif
constructTlsCertificatePrivateKeyPem ,
#if defined(ENABLE_OVERLOADING)
tlsCertificatePrivateKeyPem ,
#endif
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
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
instance B.GValue.IsGValue TlsCertificate where
toGValue :: TlsCertificate -> IO GValue
toGValue TlsCertificate
o = do
GType
gtype <- IO GType
c_g_tls_certificate_get_type
TlsCertificate -> (Ptr TlsCertificate -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsCertificate
o (GType
-> (GValue -> Ptr TlsCertificate -> IO ())
-> Ptr TlsCertificate
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TlsCertificate -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO TlsCertificate
fromGValue GValue
gv = do
Ptr TlsCertificate
ptr <- GValue -> IO (Ptr TlsCertificate)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TlsCertificate)
(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
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]
toTlsCertificate :: (MonadIO m, IsTlsCertificate o) => o -> m TlsCertificate
toTlsCertificate :: o -> m TlsCertificate
toTlsCertificate = IO TlsCertificate -> m TlsCertificate
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate
#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 "getIssuer" o = TlsCertificateGetIssuerMethodInfo
ResolveTlsCertificateMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTlsCertificateMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
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.MethodInfo 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
#endif
getTlsCertificateCertificate :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe ByteString)
getTlsCertificateCertificate :: o -> m (Maybe ByteString)
getTlsCertificateCertificate o
obj = IO (Maybe ByteString) -> m (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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"
constructTlsCertificateCertificate :: (IsTlsCertificate o, MIO.MonadIO m) => ByteString -> m (GValueConstruct o)
constructTlsCertificateCertificate :: 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
$ 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
#endif
getTlsCertificateCertificatePem :: (MonadIO m, IsTlsCertificate o) => o -> m (Maybe T.Text)
getTlsCertificateCertificatePem :: o -> m (Maybe Text)
getTlsCertificateCertificatePem o
obj = 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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"certificate-pem"
constructTlsCertificateCertificatePem :: (IsTlsCertificate o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTlsCertificateCertificatePem :: 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
$ 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
#endif
getTlsCertificateIssuer :: (MonadIO m, IsTlsCertificate o) => o -> m TlsCertificate
getTlsCertificateIssuer :: o -> m TlsCertificate
getTlsCertificateIssuer o
obj = 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
$ Text -> IO (Maybe TlsCertificate) -> IO TlsCertificate
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTlsCertificateIssuer" (IO (Maybe TlsCertificate) -> IO TlsCertificate)
-> IO (Maybe TlsCertificate) -> IO 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
constructTlsCertificateIssuer :: (IsTlsCertificate o, MIO.MonadIO m, IsTlsCertificate a) => a -> m (GValueConstruct o)
constructTlsCertificateIssuer :: 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
$ 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 = TlsCertificate
type AttrLabel TlsCertificateIssuerPropertyInfo = "issuer"
type AttrOrigin TlsCertificateIssuerPropertyInfo = TlsCertificate
attrGet = getTlsCertificateIssuer
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo TlsCertificate v
attrConstruct = constructTlsCertificateIssuer
attrClear = undefined
#endif
constructTlsCertificatePrivateKey :: (IsTlsCertificate o, MIO.MonadIO m) => ByteString -> m (GValueConstruct o)
constructTlsCertificatePrivateKey :: 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
$ 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, 'AttrClear]
type AttrBaseTypeConstraint TlsCertificatePrivateKeyPropertyInfo = IsTlsCertificate
type AttrSetTypeConstraint TlsCertificatePrivateKeyPropertyInfo = (~) ByteString
type AttrTransferTypeConstraint TlsCertificatePrivateKeyPropertyInfo = (~) ByteString
type AttrTransferType TlsCertificatePrivateKeyPropertyInfo = ByteString
type AttrGetType TlsCertificatePrivateKeyPropertyInfo = ()
type AttrLabel TlsCertificatePrivateKeyPropertyInfo = "private-key"
type AttrOrigin TlsCertificatePrivateKeyPropertyInfo = TlsCertificate
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructTlsCertificatePrivateKey
attrClear = undefined
#endif
constructTlsCertificatePrivateKeyPem :: (IsTlsCertificate o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTlsCertificatePrivateKeyPem :: 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
$ 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, 'AttrClear]
type AttrBaseTypeConstraint TlsCertificatePrivateKeyPemPropertyInfo = IsTlsCertificate
type AttrSetTypeConstraint TlsCertificatePrivateKeyPemPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint TlsCertificatePrivateKeyPemPropertyInfo = (~) T.Text
type AttrTransferType TlsCertificatePrivateKeyPemPropertyInfo = T.Text
type AttrGetType TlsCertificatePrivateKeyPemPropertyInfo = ()
type AttrLabel TlsCertificatePrivateKeyPemPropertyInfo = "private-key-pem"
type AttrOrigin TlsCertificatePrivateKeyPemPropertyInfo = TlsCertificate
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructTlsCertificatePrivateKeyPem
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsCertificate
type instance O.AttributeList TlsCertificate = TlsCertificateAttributeList
type TlsCertificateAttributeList = ('[ '("certificate", TlsCertificateCertificatePropertyInfo), '("certificatePem", TlsCertificateCertificatePemPropertyInfo), '("issuer", TlsCertificateIssuerPropertyInfo), '("privateKey", TlsCertificatePrivateKeyPropertyInfo), '("privateKeyPem", TlsCertificatePrivateKeyPemPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
tlsCertificateCertificate :: AttrLabelProxy "certificate"
tlsCertificateCertificate = AttrLabelProxy
tlsCertificateCertificatePem :: AttrLabelProxy "certificatePem"
tlsCertificateCertificatePem = AttrLabelProxy
tlsCertificateIssuer :: AttrLabelProxy "issuer"
tlsCertificateIssuer = AttrLabelProxy
tlsCertificatePrivateKey :: AttrLabelProxy "privateKey"
tlsCertificatePrivateKey = AttrLabelProxy
tlsCertificatePrivateKeyPem :: AttrLabelProxy "privateKeyPem"
tlsCertificatePrivateKeyPem = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TlsCertificate = TlsCertificateSignalList
type TlsCertificateSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_tls_certificate_new_from_file" g_tls_certificate_new_from_file ::
CString ->
Ptr (Ptr GError) ->
IO (Ptr TlsCertificate)
tlsCertificateNewFromFile ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Char]
-> m TlsCertificate
tlsCertificateNewFromFile :: 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
foreign import ccall "g_tls_certificate_new_from_files" g_tls_certificate_new_from_files ::
CString ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr TlsCertificate)
tlsCertificateNewFromFiles ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Char]
-> [Char]
-> m TlsCertificate
tlsCertificateNewFromFiles :: 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
foreign import ccall "g_tls_certificate_new_from_pem" g_tls_certificate_new_from_pem ::
CString ->
Int64 ->
Ptr (Ptr GError) ->
IO (Ptr TlsCertificate)
tlsCertificateNewFromPem ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Int64
-> m TlsCertificate
tlsCertificateNewFromPem :: 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
foreign import ccall "g_tls_certificate_get_issuer" g_tls_certificate_get_issuer ::
Ptr TlsCertificate ->
IO (Ptr TlsCertificate)
tlsCertificateGetIssuer ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a) =>
a
-> m TlsCertificate
tlsCertificateGetIssuer :: a -> m TlsCertificate
tlsCertificateGetIssuer a
cert = 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
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'
Text -> Ptr TlsCertificate -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tlsCertificateGetIssuer" 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
newObject ManagedPtr TlsCertificate -> TlsCertificate
TlsCertificate) Ptr TlsCertificate
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cert
TlsCertificate -> IO TlsCertificate
forall (m :: * -> *) a. Monad m => a -> m a
return TlsCertificate
result'
#if defined(ENABLE_OVERLOADING)
data TlsCertificateGetIssuerMethodInfo
instance (signature ~ (m TlsCertificate), MonadIO m, IsTlsCertificate a) => O.MethodInfo TlsCertificateGetIssuerMethodInfo a signature where
overloadedMethod = tlsCertificateGetIssuer
#endif
foreign import ccall "g_tls_certificate_is_same" g_tls_certificate_is_same ::
Ptr TlsCertificate ->
Ptr TlsCertificate ->
IO CInt
tlsCertificateIsSame ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a, IsTlsCertificate b) =>
a
-> b
-> m Bool
tlsCertificateIsSame :: 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.MethodInfo TlsCertificateIsSameMethodInfo a signature where
overloadedMethod = tlsCertificateIsSame
#endif
foreign import ccall "g_tls_certificate_verify" g_tls_certificate_verify ::
Ptr TlsCertificate ->
Ptr Gio.SocketConnectable.SocketConnectable ->
Ptr TlsCertificate ->
IO CUInt
tlsCertificateVerify ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsCertificate a, Gio.SocketConnectable.IsSocketConnectable b, IsTlsCertificate c) =>
a
-> Maybe (b)
-> Maybe (c)
-> m [Gio.Flags.TlsCertificateFlags]
tlsCertificateVerify :: 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.MethodInfo TlsCertificateVerifyMethodInfo a signature where
overloadedMethod = tlsCertificateVerify
#endif
foreign import ccall "g_tls_certificate_list_new_from_file" g_tls_certificate_list_new_from_file ::
CString ->
Ptr (Ptr GError) ->
IO (Ptr (GList (Ptr TlsCertificate)))
tlsCertificateListNewFromFile ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Char]
-> m [TlsCertificate]
tlsCertificateListNewFromFile :: 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