{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.TlsPassword
(
TlsPassword(..) ,
IsTlsPassword ,
toTlsPassword ,
noTlsPassword ,
#if defined(ENABLE_OVERLOADING)
ResolveTlsPasswordMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsPasswordGetDescriptionMethodInfo ,
#endif
tlsPasswordGetDescription ,
#if defined(ENABLE_OVERLOADING)
TlsPasswordGetFlagsMethodInfo ,
#endif
tlsPasswordGetFlags ,
#if defined(ENABLE_OVERLOADING)
TlsPasswordGetWarningMethodInfo ,
#endif
tlsPasswordGetWarning ,
tlsPasswordNew ,
#if defined(ENABLE_OVERLOADING)
TlsPasswordSetDescriptionMethodInfo ,
#endif
tlsPasswordSetDescription ,
#if defined(ENABLE_OVERLOADING)
TlsPasswordSetFlagsMethodInfo ,
#endif
tlsPasswordSetFlags ,
#if defined(ENABLE_OVERLOADING)
TlsPasswordSetValueMethodInfo ,
#endif
tlsPasswordSetValue ,
#if defined(ENABLE_OVERLOADING)
TlsPasswordSetValueFullMethodInfo ,
#endif
tlsPasswordSetValueFull ,
#if defined(ENABLE_OVERLOADING)
TlsPasswordSetWarningMethodInfo ,
#endif
tlsPasswordSetWarning ,
#if defined(ENABLE_OVERLOADING)
TlsPasswordDescriptionPropertyInfo ,
#endif
constructTlsPasswordDescription ,
getTlsPasswordDescription ,
setTlsPasswordDescription ,
#if defined(ENABLE_OVERLOADING)
tlsPasswordDescription ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsPasswordFlagsPropertyInfo ,
#endif
constructTlsPasswordFlags ,
getTlsPasswordFlags ,
setTlsPasswordFlags ,
#if defined(ENABLE_OVERLOADING)
tlsPasswordFlags ,
#endif
#if defined(ENABLE_OVERLOADING)
TlsPasswordWarningPropertyInfo ,
#endif
constructTlsPasswordWarning ,
getTlsPasswordWarning ,
setTlsPasswordWarning ,
#if defined(ENABLE_OVERLOADING)
tlsPasswordWarning ,
#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.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 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.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
newtype TlsPassword = TlsPassword (ManagedPtr TlsPassword)
deriving (TlsPassword -> TlsPassword -> Bool
(TlsPassword -> TlsPassword -> Bool)
-> (TlsPassword -> TlsPassword -> Bool) -> Eq TlsPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsPassword -> TlsPassword -> Bool
$c/= :: TlsPassword -> TlsPassword -> Bool
== :: TlsPassword -> TlsPassword -> Bool
$c== :: TlsPassword -> TlsPassword -> Bool
Eq)
foreign import ccall "g_tls_password_get_type"
c_g_tls_password_get_type :: IO GType
instance GObject TlsPassword where
gobjectType :: IO GType
gobjectType = IO GType
c_g_tls_password_get_type
instance B.GValue.IsGValue TlsPassword where
toGValue :: TlsPassword -> IO GValue
toGValue o :: TlsPassword
o = do
GType
gtype <- IO GType
c_g_tls_password_get_type
TlsPassword -> (Ptr TlsPassword -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsPassword
o (GType
-> (GValue -> Ptr TlsPassword -> IO ())
-> Ptr TlsPassword
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TlsPassword -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO TlsPassword
fromGValue gv :: GValue
gv = do
Ptr TlsPassword
ptr <- GValue -> IO (Ptr TlsPassword)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TlsPassword)
(ManagedPtr TlsPassword -> TlsPassword)
-> Ptr TlsPassword -> IO TlsPassword
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TlsPassword -> TlsPassword
TlsPassword Ptr TlsPassword
ptr
class (GObject o, O.IsDescendantOf TlsPassword o) => IsTlsPassword o
instance (GObject o, O.IsDescendantOf TlsPassword o) => IsTlsPassword o
instance O.HasParentTypes TlsPassword
type instance O.ParentTypes TlsPassword = '[GObject.Object.Object]
toTlsPassword :: (MonadIO m, IsTlsPassword o) => o -> m TlsPassword
toTlsPassword :: o -> m TlsPassword
toTlsPassword = IO TlsPassword -> m TlsPassword
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsPassword -> m TlsPassword)
-> (o -> IO TlsPassword) -> o -> m TlsPassword
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TlsPassword -> TlsPassword) -> o -> IO TlsPassword
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TlsPassword -> TlsPassword
TlsPassword
noTlsPassword :: Maybe TlsPassword
noTlsPassword :: Maybe TlsPassword
noTlsPassword = Maybe TlsPassword
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveTlsPasswordMethod (t :: Symbol) (o :: *) :: * where
ResolveTlsPasswordMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTlsPasswordMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTlsPasswordMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTlsPasswordMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTlsPasswordMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTlsPasswordMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTlsPasswordMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTlsPasswordMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTlsPasswordMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTlsPasswordMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTlsPasswordMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTlsPasswordMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTlsPasswordMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTlsPasswordMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTlsPasswordMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTlsPasswordMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTlsPasswordMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTlsPasswordMethod "getDescription" o = TlsPasswordGetDescriptionMethodInfo
ResolveTlsPasswordMethod "getFlags" o = TlsPasswordGetFlagsMethodInfo
ResolveTlsPasswordMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTlsPasswordMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTlsPasswordMethod "getWarning" o = TlsPasswordGetWarningMethodInfo
ResolveTlsPasswordMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTlsPasswordMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTlsPasswordMethod "setDescription" o = TlsPasswordSetDescriptionMethodInfo
ResolveTlsPasswordMethod "setFlags" o = TlsPasswordSetFlagsMethodInfo
ResolveTlsPasswordMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTlsPasswordMethod "setValue" o = TlsPasswordSetValueMethodInfo
ResolveTlsPasswordMethod "setValueFull" o = TlsPasswordSetValueFullMethodInfo
ResolveTlsPasswordMethod "setWarning" o = TlsPasswordSetWarningMethodInfo
ResolveTlsPasswordMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTlsPasswordMethod t TlsPassword, O.MethodInfo info TlsPassword p) => OL.IsLabel t (TlsPassword -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getTlsPasswordDescription :: (MonadIO m, IsTlsPassword o) => o -> m T.Text
getTlsPasswordDescription :: o -> m Text
getTlsPasswordDescription obj :: o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getTlsPasswordDescription" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO 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 "description"
setTlsPasswordDescription :: (MonadIO m, IsTlsPassword o) => o -> T.Text -> m ()
setTlsPasswordDescription :: o -> Text -> m ()
setTlsPasswordDescription obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructTlsPasswordDescription :: (IsTlsPassword o) => T.Text -> IO (GValueConstruct o)
constructTlsPasswordDescription :: Text -> IO (GValueConstruct o)
constructTlsPasswordDescription val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
#if defined(ENABLE_OVERLOADING)
data TlsPasswordDescriptionPropertyInfo
instance AttrInfo TlsPasswordDescriptionPropertyInfo where
type AttrAllowedOps TlsPasswordDescriptionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsPasswordDescriptionPropertyInfo = IsTlsPassword
type AttrSetTypeConstraint TlsPasswordDescriptionPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint TlsPasswordDescriptionPropertyInfo = (~) T.Text
type AttrTransferType TlsPasswordDescriptionPropertyInfo = T.Text
type AttrGetType TlsPasswordDescriptionPropertyInfo = T.Text
type AttrLabel TlsPasswordDescriptionPropertyInfo = "description"
type AttrOrigin TlsPasswordDescriptionPropertyInfo = TlsPassword
attrGet = getTlsPasswordDescription
attrSet = setTlsPasswordDescription
attrTransfer _ v = do
return v
attrConstruct = constructTlsPasswordDescription
attrClear = undefined
#endif
getTlsPasswordFlags :: (MonadIO m, IsTlsPassword o) => o -> m [Gio.Flags.TlsPasswordFlags]
getTlsPasswordFlags :: o -> m [TlsPasswordFlags]
getTlsPasswordFlags obj :: o
obj = IO [TlsPasswordFlags] -> m [TlsPasswordFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TlsPasswordFlags] -> m [TlsPasswordFlags])
-> IO [TlsPasswordFlags] -> m [TlsPasswordFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [TlsPasswordFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj "flags"
setTlsPasswordFlags :: (MonadIO m, IsTlsPassword o) => o -> [Gio.Flags.TlsPasswordFlags] -> m ()
setTlsPasswordFlags :: o -> [TlsPasswordFlags] -> m ()
setTlsPasswordFlags obj :: o
obj val :: [TlsPasswordFlags]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> [TlsPasswordFlags] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj "flags" [TlsPasswordFlags]
val
constructTlsPasswordFlags :: (IsTlsPassword o) => [Gio.Flags.TlsPasswordFlags] -> IO (GValueConstruct o)
constructTlsPasswordFlags :: [TlsPasswordFlags] -> IO (GValueConstruct o)
constructTlsPasswordFlags val :: [TlsPasswordFlags]
val = String -> [TlsPasswordFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags "flags" [TlsPasswordFlags]
val
#if defined(ENABLE_OVERLOADING)
data TlsPasswordFlagsPropertyInfo
instance AttrInfo TlsPasswordFlagsPropertyInfo where
type AttrAllowedOps TlsPasswordFlagsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsPasswordFlagsPropertyInfo = IsTlsPassword
type AttrSetTypeConstraint TlsPasswordFlagsPropertyInfo = (~) [Gio.Flags.TlsPasswordFlags]
type AttrTransferTypeConstraint TlsPasswordFlagsPropertyInfo = (~) [Gio.Flags.TlsPasswordFlags]
type AttrTransferType TlsPasswordFlagsPropertyInfo = [Gio.Flags.TlsPasswordFlags]
type AttrGetType TlsPasswordFlagsPropertyInfo = [Gio.Flags.TlsPasswordFlags]
type AttrLabel TlsPasswordFlagsPropertyInfo = "flags"
type AttrOrigin TlsPasswordFlagsPropertyInfo = TlsPassword
attrGet = getTlsPasswordFlags
attrSet = setTlsPasswordFlags
attrTransfer _ v = do
return v
attrConstruct = constructTlsPasswordFlags
attrClear = undefined
#endif
getTlsPasswordWarning :: (MonadIO m, IsTlsPassword o) => o -> m T.Text
getTlsPasswordWarning :: o -> m Text
getTlsPasswordWarning obj :: o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getTlsPasswordWarning" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO 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 "warning"
setTlsPasswordWarning :: (MonadIO m, IsTlsPassword o) => o -> T.Text -> m ()
setTlsPasswordWarning :: o -> Text -> m ()
setTlsPasswordWarning obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "warning" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructTlsPasswordWarning :: (IsTlsPassword o) => T.Text -> IO (GValueConstruct o)
constructTlsPasswordWarning :: Text -> IO (GValueConstruct o)
constructTlsPasswordWarning val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "warning" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
#if defined(ENABLE_OVERLOADING)
data TlsPasswordWarningPropertyInfo
instance AttrInfo TlsPasswordWarningPropertyInfo where
type AttrAllowedOps TlsPasswordWarningPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TlsPasswordWarningPropertyInfo = IsTlsPassword
type AttrSetTypeConstraint TlsPasswordWarningPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint TlsPasswordWarningPropertyInfo = (~) T.Text
type AttrTransferType TlsPasswordWarningPropertyInfo = T.Text
type AttrGetType TlsPasswordWarningPropertyInfo = T.Text
type AttrLabel TlsPasswordWarningPropertyInfo = "warning"
type AttrOrigin TlsPasswordWarningPropertyInfo = TlsPassword
attrGet = getTlsPasswordWarning
attrSet = setTlsPasswordWarning
attrTransfer _ v = do
return v
attrConstruct = constructTlsPasswordWarning
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsPassword
type instance O.AttributeList TlsPassword = TlsPasswordAttributeList
type TlsPasswordAttributeList = ('[ '("description", TlsPasswordDescriptionPropertyInfo), '("flags", TlsPasswordFlagsPropertyInfo), '("warning", TlsPasswordWarningPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
tlsPasswordDescription :: AttrLabelProxy "description"
tlsPasswordDescription = AttrLabelProxy
tlsPasswordFlags :: AttrLabelProxy "flags"
tlsPasswordFlags = AttrLabelProxy
tlsPasswordWarning :: AttrLabelProxy "warning"
tlsPasswordWarning = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TlsPassword = TlsPasswordSignalList
type TlsPasswordSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_tls_password_new" g_tls_password_new ::
CUInt ->
CString ->
IO (Ptr TlsPassword)
tlsPasswordNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Gio.Flags.TlsPasswordFlags]
-> T.Text
-> m TlsPassword
tlsPasswordNew :: [TlsPasswordFlags] -> Text -> m TlsPassword
tlsPasswordNew flags :: [TlsPasswordFlags]
flags description :: Text
description = IO TlsPassword -> m TlsPassword
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TlsPassword -> m TlsPassword)
-> IO TlsPassword -> m TlsPassword
forall a b. (a -> b) -> a -> b
$ do
let flags' :: CUInt
flags' = [TlsPasswordFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TlsPasswordFlags]
flags
CString
description' <- Text -> IO CString
textToCString Text
description
Ptr TlsPassword
result <- CUInt -> CString -> IO (Ptr TlsPassword)
g_tls_password_new CUInt
flags' CString
description'
Text -> Ptr TlsPassword -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "tlsPasswordNew" Ptr TlsPassword
result
TlsPassword
result' <- ((ManagedPtr TlsPassword -> TlsPassword)
-> Ptr TlsPassword -> IO TlsPassword
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TlsPassword -> TlsPassword
TlsPassword) Ptr TlsPassword
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
description'
TlsPassword -> IO TlsPassword
forall (m :: * -> *) a. Monad m => a -> m a
return TlsPassword
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_tls_password_get_description" g_tls_password_get_description ::
Ptr TlsPassword ->
IO CString
tlsPasswordGetDescription ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
a
-> m T.Text
tlsPasswordGetDescription :: a -> m Text
tlsPasswordGetDescription password :: a
password = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsPassword
password' <- a -> IO (Ptr TlsPassword)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
password
CString
result <- Ptr TlsPassword -> IO CString
g_tls_password_get_description Ptr TlsPassword
password'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "tlsPasswordGetDescription" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
password
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data TlsPasswordGetDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsTlsPassword a) => O.MethodInfo TlsPasswordGetDescriptionMethodInfo a signature where
overloadedMethod = tlsPasswordGetDescription
#endif
foreign import ccall "g_tls_password_get_flags" g_tls_password_get_flags ::
Ptr TlsPassword ->
IO CUInt
tlsPasswordGetFlags ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
a
-> m [Gio.Flags.TlsPasswordFlags]
tlsPasswordGetFlags :: a -> m [TlsPasswordFlags]
tlsPasswordGetFlags password :: a
password = IO [TlsPasswordFlags] -> m [TlsPasswordFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TlsPasswordFlags] -> m [TlsPasswordFlags])
-> IO [TlsPasswordFlags] -> m [TlsPasswordFlags]
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsPassword
password' <- a -> IO (Ptr TlsPassword)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
password
CUInt
result <- Ptr TlsPassword -> IO CUInt
g_tls_password_get_flags Ptr TlsPassword
password'
let result' :: [TlsPasswordFlags]
result' = CUInt -> [TlsPasswordFlags]
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
password
[TlsPasswordFlags] -> IO [TlsPasswordFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [TlsPasswordFlags]
result'
#if defined(ENABLE_OVERLOADING)
data TlsPasswordGetFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.TlsPasswordFlags]), MonadIO m, IsTlsPassword a) => O.MethodInfo TlsPasswordGetFlagsMethodInfo a signature where
overloadedMethod = tlsPasswordGetFlags
#endif
foreign import ccall "g_tls_password_get_warning" g_tls_password_get_warning ::
Ptr TlsPassword ->
IO CString
tlsPasswordGetWarning ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
a
-> m T.Text
tlsPasswordGetWarning :: a -> m Text
tlsPasswordGetWarning password :: a
password = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsPassword
password' <- a -> IO (Ptr TlsPassword)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
password
CString
result <- Ptr TlsPassword -> IO CString
g_tls_password_get_warning Ptr TlsPassword
password'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "tlsPasswordGetWarning" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
password
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data TlsPasswordGetWarningMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsTlsPassword a) => O.MethodInfo TlsPasswordGetWarningMethodInfo a signature where
overloadedMethod = tlsPasswordGetWarning
#endif
foreign import ccall "g_tls_password_set_description" g_tls_password_set_description ::
Ptr TlsPassword ->
CString ->
IO ()
tlsPasswordSetDescription ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
a
-> T.Text
-> m ()
tlsPasswordSetDescription :: a -> Text -> m ()
tlsPasswordSetDescription password :: a
password description :: Text
description = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsPassword
password' <- a -> IO (Ptr TlsPassword)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
password
CString
description' <- Text -> IO CString
textToCString Text
description
Ptr TlsPassword -> CString -> IO ()
g_tls_password_set_description Ptr TlsPassword
password' CString
description'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
password
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
description'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsPasswordSetDescriptionMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsTlsPassword a) => O.MethodInfo TlsPasswordSetDescriptionMethodInfo a signature where
overloadedMethod = tlsPasswordSetDescription
#endif
foreign import ccall "g_tls_password_set_flags" g_tls_password_set_flags ::
Ptr TlsPassword ->
CUInt ->
IO ()
tlsPasswordSetFlags ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
a
-> [Gio.Flags.TlsPasswordFlags]
-> m ()
tlsPasswordSetFlags :: a -> [TlsPasswordFlags] -> m ()
tlsPasswordSetFlags password :: a
password flags :: [TlsPasswordFlags]
flags = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsPassword
password' <- a -> IO (Ptr TlsPassword)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
password
let flags' :: CUInt
flags' = [TlsPasswordFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TlsPasswordFlags]
flags
Ptr TlsPassword -> CUInt -> IO ()
g_tls_password_set_flags Ptr TlsPassword
password' CUInt
flags'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
password
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsPasswordSetFlagsMethodInfo
instance (signature ~ ([Gio.Flags.TlsPasswordFlags] -> m ()), MonadIO m, IsTlsPassword a) => O.MethodInfo TlsPasswordSetFlagsMethodInfo a signature where
overloadedMethod = tlsPasswordSetFlags
#endif
foreign import ccall "g_tls_password_set_value" g_tls_password_set_value ::
Ptr TlsPassword ->
Ptr Word8 ->
Int64 ->
IO ()
tlsPasswordSetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
a
-> ByteString
-> m ()
tlsPasswordSetValue :: a -> ByteString -> m ()
tlsPasswordSetValue password :: a
password value :: ByteString
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let length_ :: Int64
length_ = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int64) -> Int -> Int64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
value
Ptr TlsPassword
password' <- a -> IO (Ptr TlsPassword)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
password
Ptr Word8
value' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
value
Ptr TlsPassword -> Ptr Word8 -> Int64 -> IO ()
g_tls_password_set_value Ptr TlsPassword
password' Ptr Word8
value' Int64
length_
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
password
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
value'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsPasswordSetValueMethodInfo
instance (signature ~ (ByteString -> m ()), MonadIO m, IsTlsPassword a) => O.MethodInfo TlsPasswordSetValueMethodInfo a signature where
overloadedMethod = tlsPasswordSetValue
#endif
foreign import ccall "g_tls_password_set_value_full" g_tls_password_set_value_full ::
Ptr TlsPassword ->
Ptr Word8 ->
Int64 ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
tlsPasswordSetValueFull ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
a
-> ByteString
-> Maybe (GLib.Callbacks.DestroyNotify)
-> m ()
tlsPasswordSetValueFull :: a -> ByteString -> Maybe DestroyNotify -> m ()
tlsPasswordSetValueFull password :: a
password value :: ByteString
value destroy :: Maybe DestroyNotify
destroy = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let length_ :: Int64
length_ = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int64) -> Int -> Int64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
value
Ptr TlsPassword
password' <- a -> IO (Ptr TlsPassword)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
password
Ptr Word8
value' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
value
FunPtr DestroyNotify
maybeDestroy <- case Maybe DestroyNotify
destroy of
Nothing -> FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr DestroyNotify
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just jDestroy :: DestroyNotify
jDestroy -> do
Ptr (FunPtr DestroyNotify)
ptrdestroy <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
FunPtr DestroyNotify
jDestroy' <- DestroyNotify -> IO (FunPtr DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr DestroyNotify))
-> DestroyNotify -> DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr DestroyNotify) -> Maybe (Ptr (FunPtr DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr DestroyNotify)
ptrdestroy) DestroyNotify
jDestroy)
Ptr (FunPtr DestroyNotify) -> FunPtr DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr DestroyNotify)
ptrdestroy FunPtr DestroyNotify
jDestroy'
FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr DestroyNotify
jDestroy'
Ptr TlsPassword
-> Ptr Word8 -> Int64 -> FunPtr DestroyNotify -> IO ()
g_tls_password_set_value_full Ptr TlsPassword
password' Ptr Word8
value' Int64
length_ FunPtr DestroyNotify
maybeDestroy
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
password
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
value'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsPasswordSetValueFullMethodInfo
instance (signature ~ (ByteString -> Maybe (GLib.Callbacks.DestroyNotify) -> m ()), MonadIO m, IsTlsPassword a) => O.MethodInfo TlsPasswordSetValueFullMethodInfo a signature where
overloadedMethod = tlsPasswordSetValueFull
#endif
foreign import ccall "g_tls_password_set_warning" g_tls_password_set_warning ::
Ptr TlsPassword ->
CString ->
IO ()
tlsPasswordSetWarning ::
(B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
a
-> T.Text
-> m ()
tlsPasswordSetWarning :: a -> Text -> m ()
tlsPasswordSetWarning password :: a
password warning :: Text
warning = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr TlsPassword
password' <- a -> IO (Ptr TlsPassword)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
password
CString
warning' <- Text -> IO CString
textToCString Text
warning
Ptr TlsPassword -> CString -> IO ()
g_tls_password_set_warning Ptr TlsPassword
password' CString
warning'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
password
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
warning'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TlsPasswordSetWarningMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsTlsPassword a) => O.MethodInfo TlsPasswordSetWarningMethodInfo a signature where
overloadedMethod = tlsPasswordSetWarning
#endif