{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Holds a password used in TLS.
-- 
-- /Since: 2.30/

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

module GI.Gio.Objects.TlsPassword
    ( 

-- * Exported types
    TlsPassword(..)                         ,
    IsTlsPassword                           ,
    toTlsPassword                           ,


 -- * 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"), [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"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDescription]("GI.Gio.Objects.TlsPassword#g:method:getDescription"), [getFlags]("GI.Gio.Objects.TlsPassword#g:method:getFlags"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getWarning]("GI.Gio.Objects.TlsPassword#g:method:getWarning").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDescription]("GI.Gio.Objects.TlsPassword#g:method:setDescription"), [setFlags]("GI.Gio.Objects.TlsPassword#g:method:setFlags"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setValue]("GI.Gio.Objects.TlsPassword#g:method:setValue"), [setValueFull]("GI.Gio.Objects.TlsPassword#g:method:setValueFull"), [setWarning]("GI.Gio.Objects.TlsPassword#g:method:setWarning").

#if defined(ENABLE_OVERLOADING)
    ResolveTlsPasswordMethod                ,
#endif

-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    TlsPasswordGetDescriptionMethodInfo     ,
#endif
    tlsPasswordGetDescription               ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    TlsPasswordGetFlagsMethodInfo           ,
#endif
    tlsPasswordGetFlags                     ,


-- ** getWarning #method:getWarning#

#if defined(ENABLE_OVERLOADING)
    TlsPasswordGetWarningMethodInfo         ,
#endif
    tlsPasswordGetWarning                   ,


-- ** new #method:new#

    tlsPasswordNew                          ,


-- ** setDescription #method:setDescription#

#if defined(ENABLE_OVERLOADING)
    TlsPasswordSetDescriptionMethodInfo     ,
#endif
    tlsPasswordSetDescription               ,


-- ** setFlags #method:setFlags#

#if defined(ENABLE_OVERLOADING)
    TlsPasswordSetFlagsMethodInfo           ,
#endif
    tlsPasswordSetFlags                     ,


-- ** setValue #method:setValue#

#if defined(ENABLE_OVERLOADING)
    TlsPasswordSetValueMethodInfo           ,
#endif
    tlsPasswordSetValue                     ,


-- ** setValueFull #method:setValueFull#

#if defined(ENABLE_OVERLOADING)
    TlsPasswordSetValueFullMethodInfo       ,
#endif
    tlsPasswordSetValueFull                 ,


-- ** setWarning #method:setWarning#

#if defined(ENABLE_OVERLOADING)
    TlsPasswordSetWarningMethodInfo         ,
#endif
    tlsPasswordSetWarning                   ,




 -- * Properties


-- ** description #attr:description#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    TlsPasswordDescriptionPropertyInfo      ,
#endif
    constructTlsPasswordDescription         ,
    getTlsPasswordDescription               ,
    setTlsPasswordDescription               ,
#if defined(ENABLE_OVERLOADING)
    tlsPasswordDescription                  ,
#endif


-- ** flags #attr:flags#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    TlsPasswordFlagsPropertyInfo            ,
#endif
    constructTlsPasswordFlags               ,
    getTlsPasswordFlags                     ,
    setTlsPasswordFlags                     ,
#if defined(ENABLE_OVERLOADING)
    tlsPasswordFlags                        ,
#endif


-- ** warning #attr:warning#
-- | /No description available in the introspection data./

#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.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.GHashTable as B.GHT
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.Kind as DK
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.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags

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

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

foreign import ccall "g_tls_password_get_type"
    c_g_tls_password_get_type :: IO B.Types.GType

instance B.Types.TypedObject TlsPassword where
    glibType :: IO GType
glibType = IO GType
c_g_tls_password_get_type

instance B.Types.GObject TlsPassword

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

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

-- | Cast to `TlsPassword`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toTlsPassword :: (MIO.MonadIO m, IsTlsPassword o) => o -> m TlsPassword
toTlsPassword :: forall (m :: * -> *) o.
(MonadIO m, IsTlsPassword o) =>
o -> m TlsPassword
toTlsPassword = IO TlsPassword -> m TlsPassword
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr TlsPassword -> TlsPassword
TlsPassword

-- | Convert 'TlsPassword' 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 TlsPassword) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_tls_password_get_type
    gvalueSet_ :: Ptr GValue -> Maybe TlsPassword -> IO ()
gvalueSet_ Ptr GValue
gv Maybe TlsPassword
P.Nothing = Ptr GValue -> Ptr TlsPassword -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr TlsPassword
forall a. Ptr a
FP.nullPtr :: FP.Ptr TlsPassword)
    gvalueSet_ Ptr GValue
gv (P.Just TlsPassword
obj) = TlsPassword -> (Ptr TlsPassword -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TlsPassword
obj (Ptr GValue -> Ptr TlsPassword -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe TlsPassword)
gvalueGet_ Ptr GValue
gv = do
        Ptr TlsPassword
ptr <- Ptr GValue -> IO (Ptr TlsPassword)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr TlsPassword)
        if Ptr TlsPassword
ptr Ptr TlsPassword -> Ptr TlsPassword -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TlsPassword
forall a. Ptr a
FP.nullPtr
        then TlsPassword -> Maybe TlsPassword
forall a. a -> Maybe a
P.Just (TlsPassword -> Maybe TlsPassword)
-> IO TlsPassword -> IO (Maybe TlsPassword)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe TlsPassword -> IO (Maybe TlsPassword)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TlsPassword
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveTlsPasswordMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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.OverloadedMethod 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

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

#endif

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

#endif

-- VVV Prop "description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsPassword #description
-- @
getTlsPasswordDescription :: (MonadIO m, IsTlsPassword o) => o -> m T.Text
getTlsPasswordDescription :: forall (m :: * -> *) o. (MonadIO m, IsTlsPassword o) => o -> m Text
getTlsPasswordDescription o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 Text
"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 String
"description"

-- | Set the value of the “@description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsPassword [ #description 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsPasswordDescription :: (MonadIO m, IsTlsPassword o) => o -> T.Text -> m ()
setTlsPasswordDescription :: forall (m :: * -> *) o.
(MonadIO m, IsTlsPassword o) =>
o -> Text -> m ()
setTlsPasswordDescription o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@description@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsPasswordDescription :: (IsTlsPassword o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTlsPasswordDescription :: forall o (m :: * -> *).
(IsTlsPassword o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructTlsPasswordDescription Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"description" (Text -> Maybe Text
forall a. a -> Maybe a
P.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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsPassword.description"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.32/docs/GI-Gio-Objects-TlsPassword.html#g:attr:description"
        })
#endif

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

-- | Get the value of the “@flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsPassword #flags
-- @
getTlsPasswordFlags :: (MonadIO m, IsTlsPassword o) => o -> m [Gio.Flags.TlsPasswordFlags]
getTlsPasswordFlags :: forall (m :: * -> *) o.
(MonadIO m, IsTlsPassword o) =>
o -> m [TlsPasswordFlags]
getTlsPasswordFlags o
obj = IO [TlsPasswordFlags] -> m [TlsPasswordFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"flags"

-- | Set the value of the “@flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsPassword [ #flags 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsPasswordFlags :: (MonadIO m, IsTlsPassword o) => o -> [Gio.Flags.TlsPasswordFlags] -> m ()
setTlsPasswordFlags :: forall (m :: * -> *) o.
(MonadIO m, IsTlsPassword o) =>
o -> [TlsPasswordFlags] -> m ()
setTlsPasswordFlags o
obj [TlsPasswordFlags]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> [TlsPasswordFlags] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"flags" [TlsPasswordFlags]
val

-- | Construct a `GValueConstruct` with valid value for the “@flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsPasswordFlags :: (IsTlsPassword o, MIO.MonadIO m) => [Gio.Flags.TlsPasswordFlags] -> m (GValueConstruct o)
constructTlsPasswordFlags :: forall o (m :: * -> *).
(IsTlsPassword o, MonadIO m) =>
[TlsPasswordFlags] -> m (GValueConstruct o)
constructTlsPasswordFlags [TlsPasswordFlags]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> [TlsPasswordFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsPassword.flags"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.32/docs/GI-Gio-Objects-TlsPassword.html#g:attr:flags"
        })
#endif

-- VVV Prop "warning"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@warning@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tlsPassword #warning
-- @
getTlsPasswordWarning :: (MonadIO m, IsTlsPassword o) => o -> m T.Text
getTlsPasswordWarning :: forall (m :: * -> *) o. (MonadIO m, IsTlsPassword o) => o -> m Text
getTlsPasswordWarning o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 Text
"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 String
"warning"

-- | Set the value of the “@warning@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tlsPassword [ #warning 'Data.GI.Base.Attributes.:=' value ]
-- @
setTlsPasswordWarning :: (MonadIO m, IsTlsPassword o) => o -> T.Text -> m ()
setTlsPasswordWarning :: forall (m :: * -> *) o.
(MonadIO m, IsTlsPassword o) =>
o -> Text -> m ()
setTlsPasswordWarning o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"warning" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@warning@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTlsPasswordWarning :: (IsTlsPassword o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTlsPasswordWarning :: forall o (m :: * -> *).
(IsTlsPassword o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructTlsPasswordWarning Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"warning" (Text -> Maybe Text
forall a. a -> Maybe a
P.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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.TlsPassword.warning"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.32/docs/GI-Gio-Objects-TlsPassword.html#g:attr:warning"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TlsPassword
type instance O.AttributeList TlsPassword = TlsPasswordAttributeList
type TlsPasswordAttributeList = ('[ '("description", TlsPasswordDescriptionPropertyInfo), '("flags", TlsPasswordFlagsPropertyInfo), '("warning", TlsPasswordWarningPropertyInfo)] :: [(Symbol, DK.Type)])
#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, DK.Type)])

#endif

-- method TlsPassword::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPasswordFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the password flags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "description of what the password is for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "TlsPassword" })
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_password_new" g_tls_password_new :: 
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "TlsPasswordFlags"})
    CString ->                              -- description : TBasicType TUTF8
    IO (Ptr TlsPassword)

-- | Create a new t'GI.Gio.Objects.TlsPassword.TlsPassword' object.
tlsPasswordNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Gio.Flags.TlsPasswordFlags]
    -- ^ /@flags@/: the password flags
    -> T.Text
    -- ^ /@description@/: description of what the password is for
    -> m TlsPassword
    -- ^ __Returns:__ The newly allocated password object
tlsPasswordNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[TlsPasswordFlags] -> Text -> m TlsPassword
tlsPasswordNew [TlsPasswordFlags]
flags Text
description = IO TlsPassword -> m TlsPassword
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TlsPassword
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method TlsPassword::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "password"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPassword" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsPassword object"
--                 , 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_password_get_description" g_tls_password_get_description :: 
    Ptr TlsPassword ->                      -- password : TInterface (Name {namespace = "Gio", name = "TlsPassword"})
    IO CString

-- | Get a description string about what the password will be used for.
-- 
-- /Since: 2.30/
tlsPasswordGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
    a
    -- ^ /@password@/: a t'GI.Gio.Objects.TlsPassword.TlsPassword' object
    -> m T.Text
    -- ^ __Returns:__ The description of the password.
tlsPasswordGetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsPassword a) =>
a -> m Text
tlsPasswordGetDescription a
password = IO Text -> m Text
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod TlsPasswordGetDescriptionMethodInfo a signature where
    overloadedMethod = tlsPasswordGetDescription

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


#endif

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

foreign import ccall "g_tls_password_get_flags" g_tls_password_get_flags :: 
    Ptr TlsPassword ->                      -- password : TInterface (Name {namespace = "Gio", name = "TlsPassword"})
    IO CUInt

-- | Get flags about the password.
-- 
-- /Since: 2.30/
tlsPasswordGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
    a
    -- ^ /@password@/: a t'GI.Gio.Objects.TlsPassword.TlsPassword' object
    -> m [Gio.Flags.TlsPasswordFlags]
    -- ^ __Returns:__ The flags about the password.
tlsPasswordGetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsPassword a) =>
a -> m [TlsPasswordFlags]
tlsPasswordGetFlags a
password = IO [TlsPasswordFlags] -> m [TlsPasswordFlags]
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod TlsPasswordGetFlagsMethodInfo a signature where
    overloadedMethod = tlsPasswordGetFlags

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


#endif

-- method TlsPassword::get_warning
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "password"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPassword" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsPassword object"
--                 , 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_password_get_warning" g_tls_password_get_warning :: 
    Ptr TlsPassword ->                      -- password : TInterface (Name {namespace = "Gio", name = "TlsPassword"})
    IO CString

-- | Get a user readable translated warning. Usually this warning is a
-- representation of the password flags returned from
-- 'GI.Gio.Objects.TlsPassword.tlsPasswordGetFlags'.
-- 
-- /Since: 2.30/
tlsPasswordGetWarning ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
    a
    -- ^ /@password@/: a t'GI.Gio.Objects.TlsPassword.TlsPassword' object
    -> m T.Text
    -- ^ __Returns:__ The warning.
tlsPasswordGetWarning :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsPassword a) =>
a -> m Text
tlsPasswordGetWarning a
password = IO Text -> m Text
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.OverloadedMethod TlsPasswordGetWarningMethodInfo a signature where
    overloadedMethod = tlsPasswordGetWarning

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


#endif

-- method TlsPassword::set_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "password"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPassword" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsPassword object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The description of the password"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_password_set_description" g_tls_password_set_description :: 
    Ptr TlsPassword ->                      -- password : TInterface (Name {namespace = "Gio", name = "TlsPassword"})
    CString ->                              -- description : TBasicType TUTF8
    IO ()

-- | Set a description string about what the password will be used for.
-- 
-- /Since: 2.30/
tlsPasswordSetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
    a
    -- ^ /@password@/: a t'GI.Gio.Objects.TlsPassword.TlsPassword' object
    -> T.Text
    -- ^ /@description@/: The description of the password
    -> m ()
tlsPasswordSetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsPassword a) =>
a -> Text -> m ()
tlsPasswordSetDescription a
password Text
description = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod TlsPasswordSetDescriptionMethodInfo a signature where
    overloadedMethod = tlsPasswordSetDescription

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


#endif

-- method TlsPassword::set_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "password"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPassword" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsPassword object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPasswordFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The flags about the password"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_password_set_flags" g_tls_password_set_flags :: 
    Ptr TlsPassword ->                      -- password : TInterface (Name {namespace = "Gio", name = "TlsPassword"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "TlsPasswordFlags"})
    IO ()

-- | Set flags about the password.
-- 
-- /Since: 2.30/
tlsPasswordSetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
    a
    -- ^ /@password@/: a t'GI.Gio.Objects.TlsPassword.TlsPassword' object
    -> [Gio.Flags.TlsPasswordFlags]
    -- ^ /@flags@/: The flags about the password
    -> m ()
tlsPasswordSetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsPassword a) =>
a -> [TlsPasswordFlags] -> m ()
tlsPasswordSetFlags a
password [TlsPasswordFlags]
flags = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod TlsPasswordSetFlagsMethodInfo a signature where
    overloadedMethod = tlsPasswordSetFlags

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


#endif

-- method TlsPassword::set_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "password"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPassword" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsPassword object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new password value"
--                 , 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 the password, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of the password, or -1"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_password_set_value" g_tls_password_set_value :: 
    Ptr TlsPassword ->                      -- password : TInterface (Name {namespace = "Gio", name = "TlsPassword"})
    Ptr Word8 ->                            -- value : TCArray False (-1) 2 (TBasicType TUInt8)
    Int64 ->                                -- length : TBasicType TInt64
    IO ()

-- | Set the value for this password. The /@value@/ will be copied by the password
-- object.
-- 
-- Specify the /@length@/, for a non-nul-terminated password. Pass -1 as
-- /@length@/ if using a nul-terminated password, and /@length@/ will be
-- calculated automatically. (Note that the terminating nul is not
-- considered part of the password in this case.)
-- 
-- /Since: 2.30/
tlsPasswordSetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
    a
    -- ^ /@password@/: a t'GI.Gio.Objects.TlsPassword.TlsPassword' object
    -> ByteString
    -- ^ /@value@/: the new password value
    -> m ()
tlsPasswordSetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsPassword a) =>
a -> ByteString -> m ()
tlsPasswordSetValue a
password ByteString
value = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TlsPasswordSetValueMethodInfo
instance (signature ~ (ByteString -> m ()), MonadIO m, IsTlsPassword a) => O.OverloadedMethod TlsPasswordSetValueMethodInfo a signature where
    overloadedMethod = tlsPasswordSetValue

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


#endif

-- method TlsPassword::set_value_full
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "password"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPassword" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsPassword object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value for the password"
--                 , 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 the password, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a function to use to free the password."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of the password, or -1"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_password_set_value_full" g_tls_password_set_value_full :: 
    Ptr TlsPassword ->                      -- password : TInterface (Name {namespace = "Gio", name = "TlsPassword"})
    Ptr Word8 ->                            -- value : TCArray False (-1) 2 (TBasicType TUInt8)
    Int64 ->                                -- length : TBasicType TInt64
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Provide the value for this password.
-- 
-- The /@value@/ will be owned by the password object, and later freed using
-- the /@destroy@/ function callback.
-- 
-- Specify the /@length@/, for a non-nul-terminated password. Pass -1 as
-- /@length@/ if using a nul-terminated password, and /@length@/ will be
-- calculated automatically. (Note that the terminating nul is not
-- considered part of the password in this case.)
-- 
-- /Since: 2.30/
tlsPasswordSetValueFull ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
    a
    -- ^ /@password@/: a t'GI.Gio.Objects.TlsPassword.TlsPassword' object
    -> ByteString
    -- ^ /@value@/: the value for the password
    -> Maybe (GLib.Callbacks.DestroyNotify)
    -- ^ /@destroy@/: a function to use to free the password.
    -> m ()
tlsPasswordSetValueFull :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsPassword a) =>
a -> ByteString -> Maybe DestroyNotify -> m ()
tlsPasswordSetValueFull a
password ByteString
value Maybe DestroyNotify
destroy = IO () -> m ()
forall a. IO a -> m a
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
        Maybe DestroyNotify
Nothing -> FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall a. a -> IO a
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 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 a. a -> IO a
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 a. a -> IO a
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.OverloadedMethod TlsPasswordSetValueFullMethodInfo a signature where
    overloadedMethod = tlsPasswordSetValueFull

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


#endif

-- method TlsPassword::set_warning
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "password"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TlsPassword" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTlsPassword object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "warning"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The user readable warning"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_tls_password_set_warning" g_tls_password_set_warning :: 
    Ptr TlsPassword ->                      -- password : TInterface (Name {namespace = "Gio", name = "TlsPassword"})
    CString ->                              -- warning : TBasicType TUTF8
    IO ()

-- | Set a user readable translated warning. Usually this warning is a
-- representation of the password flags returned from
-- 'GI.Gio.Objects.TlsPassword.tlsPasswordGetFlags'.
-- 
-- /Since: 2.30/
tlsPasswordSetWarning ::
    (B.CallStack.HasCallStack, MonadIO m, IsTlsPassword a) =>
    a
    -- ^ /@password@/: a t'GI.Gio.Objects.TlsPassword.TlsPassword' object
    -> T.Text
    -- ^ /@warning@/: The user readable warning
    -> m ()
tlsPasswordSetWarning :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTlsPassword a) =>
a -> Text -> m ()
tlsPasswordSetWarning a
password Text
warning = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod TlsPasswordSetWarningMethodInfo a signature where
    overloadedMethod = tlsPasswordSetWarning

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


#endif