{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents a plain text credential.

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

module GI.Ggit.Objects.CredPlaintext
    ( 

-- * Exported types
    CredPlaintext(..)                       ,
    IsCredPlaintext                         ,
    toCredPlaintext                         ,


 -- * 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"), [init]("GI.Gio.Interfaces.Initable#g:method:init"), [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"), [getPassword]("GI.Ggit.Objects.CredPlaintext#g:method:getPassword"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getUsername]("GI.Ggit.Objects.CredPlaintext#g:method:getUsername").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveCredPlaintextMethod              ,
#endif

-- ** getPassword #method:getPassword#

#if defined(ENABLE_OVERLOADING)
    CredPlaintextGetPasswordMethodInfo      ,
#endif
    credPlaintextGetPassword                ,


-- ** getUsername #method:getUsername#

#if defined(ENABLE_OVERLOADING)
    CredPlaintextGetUsernameMethodInfo      ,
#endif
    credPlaintextGetUsername                ,


-- ** new #method:new#

    credPlaintextNew                        ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    CredPlaintextPasswordPropertyInfo       ,
#endif
    constructCredPlaintextPassword          ,
#if defined(ENABLE_OVERLOADING)
    credPlaintextPassword                   ,
#endif
    getCredPlaintextPassword                ,


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

#if defined(ENABLE_OVERLOADING)
    CredPlaintextUsernamePropertyInfo       ,
#endif
    constructCredPlaintextUsername          ,
#if defined(ENABLE_OVERLOADING)
    credPlaintextUsername                   ,
#endif
    getCredPlaintextUsername                ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Ggit.Objects.Cred as Ggit.Cred
import {-# SOURCE #-} qualified GI.Ggit.Objects.Native as Ggit.Native
import {-# SOURCE #-} qualified GI.Ggit.Objects.ObjectFactoryBase as Ggit.ObjectFactoryBase
import qualified GI.Gio.Interfaces.Initable as Gio.Initable

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

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

foreign import ccall "ggit_cred_plaintext_get_type"
    c_ggit_cred_plaintext_get_type :: IO B.Types.GType

instance B.Types.TypedObject CredPlaintext where
    glibType :: IO GType
glibType = IO GType
c_ggit_cred_plaintext_get_type

instance B.Types.GObject CredPlaintext

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

instance O.HasParentTypes CredPlaintext
type instance O.ParentTypes CredPlaintext = '[Ggit.Cred.Cred, Ggit.Native.Native, Ggit.ObjectFactoryBase.ObjectFactoryBase, GObject.Object.Object, Gio.Initable.Initable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveCredPlaintextMethod (t :: Symbol) (o :: *) :: * where
    ResolveCredPlaintextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCredPlaintextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCredPlaintextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCredPlaintextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCredPlaintextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCredPlaintextMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveCredPlaintextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCredPlaintextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCredPlaintextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCredPlaintextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCredPlaintextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCredPlaintextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCredPlaintextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCredPlaintextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCredPlaintextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCredPlaintextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCredPlaintextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCredPlaintextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCredPlaintextMethod "getPassword" o = CredPlaintextGetPasswordMethodInfo
    ResolveCredPlaintextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCredPlaintextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCredPlaintextMethod "getUsername" o = CredPlaintextGetUsernameMethodInfo
    ResolveCredPlaintextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCredPlaintextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCredPlaintextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCredPlaintextMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveCredPlaintextMethod t CredPlaintext, O.OverloadedMethod info CredPlaintext p) => OL.IsLabel t (CredPlaintext -> 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 ~ ResolveCredPlaintextMethod t CredPlaintext, O.OverloadedMethod info CredPlaintext p, R.HasField t CredPlaintext p) => R.HasField t CredPlaintext p where
    getField = O.overloadedMethod @info

#endif

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

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data CredPlaintextPasswordPropertyInfo
instance AttrInfo CredPlaintextPasswordPropertyInfo where
    type AttrAllowedOps CredPlaintextPasswordPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CredPlaintextPasswordPropertyInfo = IsCredPlaintext
    type AttrSetTypeConstraint CredPlaintextPasswordPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CredPlaintextPasswordPropertyInfo = (~) T.Text
    type AttrTransferType CredPlaintextPasswordPropertyInfo = T.Text
    type AttrGetType CredPlaintextPasswordPropertyInfo = T.Text
    type AttrLabel CredPlaintextPasswordPropertyInfo = "password"
    type AttrOrigin CredPlaintextPasswordPropertyInfo = CredPlaintext
    attrGet = getCredPlaintextPassword
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructCredPlaintextPassword
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CredPlaintext.password"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.11/docs/GI-Ggit-Objects-CredPlaintext.html#g:attr:password"
        })
#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data CredPlaintextUsernamePropertyInfo
instance AttrInfo CredPlaintextUsernamePropertyInfo where
    type AttrAllowedOps CredPlaintextUsernamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CredPlaintextUsernamePropertyInfo = IsCredPlaintext
    type AttrSetTypeConstraint CredPlaintextUsernamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CredPlaintextUsernamePropertyInfo = (~) T.Text
    type AttrTransferType CredPlaintextUsernamePropertyInfo = T.Text
    type AttrGetType CredPlaintextUsernamePropertyInfo = T.Text
    type AttrLabel CredPlaintextUsernamePropertyInfo = "username"
    type AttrOrigin CredPlaintextUsernamePropertyInfo = CredPlaintext
    attrGet = getCredPlaintextUsername
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructCredPlaintextUsername
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CredPlaintext.username"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.11/docs/GI-Ggit-Objects-CredPlaintext.html#g:attr:username"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CredPlaintext
type instance O.AttributeList CredPlaintext = CredPlaintextAttributeList
type CredPlaintextAttributeList = ('[ '("native", Ggit.Native.NativeNativePropertyInfo), '("password", CredPlaintextPasswordPropertyInfo), '("username", CredPlaintextUsernamePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
credPlaintextPassword :: AttrLabelProxy "password"
credPlaintextPassword = AttrLabelProxy

credPlaintextUsername :: AttrLabelProxy "username"
credPlaintextUsername = AttrLabelProxy

#endif

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

#endif

-- method CredPlaintext::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "username"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "password"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Ggit" , name = "CredPlaintext" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_cred_plaintext_new" ggit_cred_plaintext_new :: 
    CString ->                              -- username : TBasicType TUTF8
    CString ->                              -- password : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CredPlaintext)

-- | /No description available in the introspection data./
credPlaintextNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -> T.Text
    -> m CredPlaintext
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
credPlaintextNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Text -> m CredPlaintext
credPlaintextNew Text
username Text
password = IO CredPlaintext -> m CredPlaintext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CredPlaintext -> m CredPlaintext)
-> IO CredPlaintext -> m CredPlaintext
forall a b. (a -> b) -> a -> b
$ do
    CString
username' <- Text -> IO CString
textToCString Text
username
    CString
password' <- Text -> IO CString
textToCString Text
password
    IO CredPlaintext -> IO () -> IO CredPlaintext
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CredPlaintext
result <- (Ptr (Ptr GError) -> IO (Ptr CredPlaintext))
-> IO (Ptr CredPlaintext)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CredPlaintext))
 -> IO (Ptr CredPlaintext))
-> (Ptr (Ptr GError) -> IO (Ptr CredPlaintext))
-> IO (Ptr CredPlaintext)
forall a b. (a -> b) -> a -> b
$ CString -> CString -> Ptr (Ptr GError) -> IO (Ptr CredPlaintext)
ggit_cred_plaintext_new CString
username' CString
password'
        Text -> Ptr CredPlaintext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"credPlaintextNew" Ptr CredPlaintext
result
        CredPlaintext
result' <- ((ManagedPtr CredPlaintext -> CredPlaintext)
-> Ptr CredPlaintext -> IO CredPlaintext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr CredPlaintext -> CredPlaintext
CredPlaintext) Ptr CredPlaintext
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
username'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
password'
        CredPlaintext -> IO CredPlaintext
forall (m :: * -> *) a. Monad m => a -> m a
return CredPlaintext
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
username'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
password'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method CredPlaintext::get_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cred"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CredPlaintext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , 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 "ggit_cred_plaintext_get_password" ggit_cred_plaintext_get_password :: 
    Ptr CredPlaintext ->                    -- cred : TInterface (Name {namespace = "Ggit", name = "CredPlaintext"})
    IO CString

-- | /No description available in the introspection data./
credPlaintextGetPassword ::
    (B.CallStack.HasCallStack, MonadIO m, IsCredPlaintext a) =>
    a
    -> m T.Text
credPlaintextGetPassword :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCredPlaintext a) =>
a -> m Text
credPlaintextGetPassword a
cred = 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 CredPlaintext
cred' <- a -> IO (Ptr CredPlaintext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cred
    CString
result <- Ptr CredPlaintext -> IO CString
ggit_cred_plaintext_get_password Ptr CredPlaintext
cred'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"credPlaintextGetPassword" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cred
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data CredPlaintextGetPasswordMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsCredPlaintext a) => O.OverloadedMethod CredPlaintextGetPasswordMethodInfo a signature where
    overloadedMethod = credPlaintextGetPassword

instance O.OverloadedMethodInfo CredPlaintextGetPasswordMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CredPlaintext.credPlaintextGetPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.11/docs/GI-Ggit-Objects-CredPlaintext.html#v:credPlaintextGetPassword"
        })


#endif

-- method CredPlaintext::get_username
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cred"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CredPlaintext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , 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 "ggit_cred_plaintext_get_username" ggit_cred_plaintext_get_username :: 
    Ptr CredPlaintext ->                    -- cred : TInterface (Name {namespace = "Ggit", name = "CredPlaintext"})
    IO CString

-- | /No description available in the introspection data./
credPlaintextGetUsername ::
    (B.CallStack.HasCallStack, MonadIO m, IsCredPlaintext a) =>
    a
    -> m T.Text
credPlaintextGetUsername :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCredPlaintext a) =>
a -> m Text
credPlaintextGetUsername a
cred = 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 CredPlaintext
cred' <- a -> IO (Ptr CredPlaintext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cred
    CString
result <- Ptr CredPlaintext -> IO CString
ggit_cred_plaintext_get_username Ptr CredPlaintext
cred'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"credPlaintextGetUsername" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cred
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data CredPlaintextGetUsernameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsCredPlaintext a) => O.OverloadedMethod CredPlaintextGetUsernameMethodInfo a signature where
    overloadedMethod = credPlaintextGetUsername

instance O.OverloadedMethodInfo CredPlaintextGetUsernameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CredPlaintext.credPlaintextGetUsername",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.11/docs/GI-Ggit-Objects-CredPlaintext.html#v:credPlaintextGetUsername"
        })


#endif