{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- PPP-over-Ethernet Settings

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

module GI.NM.Objects.SettingPppoe
    ( 

-- * Exported types
    SettingPppoe(..)                        ,
    IsSettingPppoe                          ,
    toSettingPppoe                          ,


 -- * 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"), [compare]("GI.NM.Objects.Setting#g:method:compare"), [diff]("GI.NM.Objects.Setting#g:method:diff"), [duplicate]("GI.NM.Objects.Setting#g:method:duplicate"), [enumerateValues]("GI.NM.Objects.Setting#g:method:enumerateValues"), [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"), [optionClearByName]("GI.NM.Objects.Setting#g:method:optionClearByName"), [optionGet]("GI.NM.Objects.Setting#g:method:optionGet"), [optionGetAllNames]("GI.NM.Objects.Setting#g:method:optionGetAllNames"), [optionGetBoolean]("GI.NM.Objects.Setting#g:method:optionGetBoolean"), [optionGetUint32]("GI.NM.Objects.Setting#g:method:optionGetUint32"), [optionSet]("GI.NM.Objects.Setting#g:method:optionSet"), [optionSetBoolean]("GI.NM.Objects.Setting#g:method:optionSetBoolean"), [optionSetUint32]("GI.NM.Objects.Setting#g:method:optionSetUint32"), [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"), [toString]("GI.NM.Objects.Setting#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [verify]("GI.NM.Objects.Setting#g:method:verify"), [verifySecrets]("GI.NM.Objects.Setting#g:method:verifySecrets"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDbusPropertyType]("GI.NM.Objects.Setting#g:method:getDbusPropertyType"), [getName]("GI.NM.Objects.Setting#g:method:getName"), [getParent]("GI.NM.Objects.SettingPppoe#g:method:getParent"), [getPassword]("GI.NM.Objects.SettingPppoe#g:method:getPassword"), [getPasswordFlags]("GI.NM.Objects.SettingPppoe#g:method:getPasswordFlags"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSecretFlags]("GI.NM.Objects.Setting#g:method:getSecretFlags"), [getService]("GI.NM.Objects.SettingPppoe#g:method:getService"), [getUsername]("GI.NM.Objects.SettingPppoe#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"), [setSecretFlags]("GI.NM.Objects.Setting#g:method:setSecretFlags").

#if defined(ENABLE_OVERLOADING)
    ResolveSettingPppoeMethod               ,
#endif

-- ** getParent #method:getParent#

#if defined(ENABLE_OVERLOADING)
    SettingPppoeGetParentMethodInfo         ,
#endif
    settingPppoeGetParent                   ,


-- ** getPassword #method:getPassword#

#if defined(ENABLE_OVERLOADING)
    SettingPppoeGetPasswordMethodInfo       ,
#endif
    settingPppoeGetPassword                 ,


-- ** getPasswordFlags #method:getPasswordFlags#

#if defined(ENABLE_OVERLOADING)
    SettingPppoeGetPasswordFlagsMethodInfo  ,
#endif
    settingPppoeGetPasswordFlags            ,


-- ** getService #method:getService#

#if defined(ENABLE_OVERLOADING)
    SettingPppoeGetServiceMethodInfo        ,
#endif
    settingPppoeGetService                  ,


-- ** getUsername #method:getUsername#

#if defined(ENABLE_OVERLOADING)
    SettingPppoeGetUsernameMethodInfo       ,
#endif
    settingPppoeGetUsername                 ,


-- ** new #method:new#

    settingPppoeNew                         ,




 -- * Properties


-- ** parent #attr:parent#
-- | If given, specifies the parent interface name on which this PPPoE
-- connection should be created.  If this property is not specified,
-- the connection is activated on the interface specified in
-- [SettingConnection:interfaceName]("GI.NM.Objects.SettingConnection#g:attr:interfaceName") of t'GI.NM.Objects.SettingConnection.SettingConnection'.
-- 
-- /Since: 1.10/

#if defined(ENABLE_OVERLOADING)
    SettingPppoeParentPropertyInfo          ,
#endif
    clearSettingPppoeParent                 ,
    constructSettingPppoeParent             ,
    getSettingPppoeParent                   ,
    setSettingPppoeParent                   ,
#if defined(ENABLE_OVERLOADING)
    settingPppoeParent                      ,
#endif


-- ** password #attr:password#
-- | Password used to authenticate with the PPPoE service.

#if defined(ENABLE_OVERLOADING)
    SettingPppoePasswordPropertyInfo        ,
#endif
    clearSettingPppoePassword               ,
    constructSettingPppoePassword           ,
    getSettingPppoePassword                 ,
    setSettingPppoePassword                 ,
#if defined(ENABLE_OVERLOADING)
    settingPppoePassword                    ,
#endif


-- ** passwordFlags #attr:passwordFlags#
-- | Flags indicating how to handle the [SettingPppoe:password]("GI.NM.Objects.SettingPppoe#g:attr:password") property.

#if defined(ENABLE_OVERLOADING)
    SettingPppoePasswordFlagsPropertyInfo   ,
#endif
    constructSettingPppoePasswordFlags      ,
    getSettingPppoePasswordFlags            ,
    setSettingPppoePasswordFlags            ,
#if defined(ENABLE_OVERLOADING)
    settingPppoePasswordFlags               ,
#endif


-- ** service #attr:service#
-- | If specified, instruct PPPoE to only initiate sessions with access
-- concentrators that provide the specified service.  For most providers,
-- this should be left blank.  It is only required if there are multiple
-- access concentrators or a specific service is known to be required.

#if defined(ENABLE_OVERLOADING)
    SettingPppoeServicePropertyInfo         ,
#endif
    clearSettingPppoeService                ,
    constructSettingPppoeService            ,
    getSettingPppoeService                  ,
    setSettingPppoeService                  ,
#if defined(ENABLE_OVERLOADING)
    settingPppoeService                     ,
#endif


-- ** username #attr:username#
-- | Username used to authenticate with the PPPoE service.

#if defined(ENABLE_OVERLOADING)
    SettingPppoeUsernamePropertyInfo        ,
#endif
    clearSettingPppoeUsername               ,
    constructSettingPppoeUsername           ,
    getSettingPppoeUsername                 ,
    setSettingPppoeUsername                 ,
#if defined(ENABLE_OVERLOADING)
    settingPppoeUsername                    ,
#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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.NM.Callbacks as NM.Callbacks
import {-# SOURCE #-} qualified GI.NM.Enums as NM.Enums
import {-# SOURCE #-} qualified GI.NM.Flags as NM.Flags
import {-# SOURCE #-} qualified GI.NM.Interfaces.Connection as NM.Connection
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
import {-# SOURCE #-} qualified GI.NM.Objects.Setting8021x as NM.Setting8021x
import {-# SOURCE #-} qualified GI.NM.Objects.SettingAdsl as NM.SettingAdsl
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBluetooth as NM.SettingBluetooth
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBond as NM.SettingBond
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridge as NM.SettingBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridgePort as NM.SettingBridgePort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingCdma as NM.SettingCdma
import {-# SOURCE #-} qualified GI.NM.Objects.SettingConnection as NM.SettingConnection
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDcb as NM.SettingDcb
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDummy as NM.SettingDummy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGeneric as NM.SettingGeneric
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGsm as NM.SettingGsm
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP4Config as NM.SettingIP4Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP6Config as NM.SettingIP6Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPConfig as NM.SettingIPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPTunnel as NM.SettingIPTunnel
import {-# SOURCE #-} qualified GI.NM.Objects.SettingInfiniband as NM.SettingInfiniband
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacsec as NM.SettingMacsec
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacvlan as NM.SettingMacvlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOlpcMesh as NM.SettingOlpcMesh
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsBridge as NM.SettingOvsBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsInterface as NM.SettingOvsInterface
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPatch as NM.SettingOvsPatch
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPort as NM.SettingOvsPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPpp as NM.SettingPpp
import {-# SOURCE #-} qualified GI.NM.Objects.SettingProxy as NM.SettingProxy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingSerial as NM.SettingSerial
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTCConfig as NM.SettingTCConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeam as NM.SettingTeam
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeamPort as NM.SettingTeamPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTun as NM.SettingTun
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVlan as NM.SettingVlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVpn as NM.SettingVpn
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVxlan as NM.SettingVxlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWimax as NM.SettingWimax
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWired as NM.SettingWired
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWireless as NM.SettingWireless
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWirelessSecurity as NM.SettingWirelessSecurity
import {-# SOURCE #-} qualified GI.NM.Structs.BridgeVlan as NM.BridgeVlan
import {-# SOURCE #-} qualified GI.NM.Structs.IPAddress as NM.IPAddress
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoute as NM.IPRoute
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoutingRule as NM.IPRoutingRule
import {-# SOURCE #-} qualified GI.NM.Structs.Range as NM.Range
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.NM.Flags as NM.Flags
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting

#endif

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

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

foreign import ccall "nm_setting_pppoe_get_type"
    c_nm_setting_pppoe_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingPppoe where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_pppoe_get_type

instance B.Types.GObject SettingPppoe

-- | Type class for types which can be safely cast to t'SettingPppoe', for instance with `toSettingPppoe`.
class (SP.GObject o, O.IsDescendantOf SettingPppoe o) => IsSettingPppoe o
instance (SP.GObject o, O.IsDescendantOf SettingPppoe o) => IsSettingPppoe o

instance O.HasParentTypes SettingPppoe
type instance O.ParentTypes SettingPppoe = '[NM.Setting.Setting, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSettingPppoeMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSettingPppoeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSettingPppoeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSettingPppoeMethod "compare" o = NM.Setting.SettingCompareMethodInfo
    ResolveSettingPppoeMethod "diff" o = NM.Setting.SettingDiffMethodInfo
    ResolveSettingPppoeMethod "duplicate" o = NM.Setting.SettingDuplicateMethodInfo
    ResolveSettingPppoeMethod "enumerateValues" o = NM.Setting.SettingEnumerateValuesMethodInfo
    ResolveSettingPppoeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSettingPppoeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSettingPppoeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSettingPppoeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSettingPppoeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSettingPppoeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSettingPppoeMethod "optionClearByName" o = NM.Setting.SettingOptionClearByNameMethodInfo
    ResolveSettingPppoeMethod "optionGet" o = NM.Setting.SettingOptionGetMethodInfo
    ResolveSettingPppoeMethod "optionGetAllNames" o = NM.Setting.SettingOptionGetAllNamesMethodInfo
    ResolveSettingPppoeMethod "optionGetBoolean" o = NM.Setting.SettingOptionGetBooleanMethodInfo
    ResolveSettingPppoeMethod "optionGetUint32" o = NM.Setting.SettingOptionGetUint32MethodInfo
    ResolveSettingPppoeMethod "optionSet" o = NM.Setting.SettingOptionSetMethodInfo
    ResolveSettingPppoeMethod "optionSetBoolean" o = NM.Setting.SettingOptionSetBooleanMethodInfo
    ResolveSettingPppoeMethod "optionSetUint32" o = NM.Setting.SettingOptionSetUint32MethodInfo
    ResolveSettingPppoeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSettingPppoeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSettingPppoeMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSettingPppoeMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSettingPppoeMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSettingPppoeMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSettingPppoeMethod "toString" o = NM.Setting.SettingToStringMethodInfo
    ResolveSettingPppoeMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSettingPppoeMethod "verify" o = NM.Setting.SettingVerifyMethodInfo
    ResolveSettingPppoeMethod "verifySecrets" o = NM.Setting.SettingVerifySecretsMethodInfo
    ResolveSettingPppoeMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSettingPppoeMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSettingPppoeMethod "getDbusPropertyType" o = NM.Setting.SettingGetDbusPropertyTypeMethodInfo
    ResolveSettingPppoeMethod "getName" o = NM.Setting.SettingGetNameMethodInfo
    ResolveSettingPppoeMethod "getParent" o = SettingPppoeGetParentMethodInfo
    ResolveSettingPppoeMethod "getPassword" o = SettingPppoeGetPasswordMethodInfo
    ResolveSettingPppoeMethod "getPasswordFlags" o = SettingPppoeGetPasswordFlagsMethodInfo
    ResolveSettingPppoeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingPppoeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingPppoeMethod "getSecretFlags" o = NM.Setting.SettingGetSecretFlagsMethodInfo
    ResolveSettingPppoeMethod "getService" o = SettingPppoeGetServiceMethodInfo
    ResolveSettingPppoeMethod "getUsername" o = SettingPppoeGetUsernameMethodInfo
    ResolveSettingPppoeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingPppoeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingPppoeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingPppoeMethod "setSecretFlags" o = NM.Setting.SettingSetSecretFlagsMethodInfo
    ResolveSettingPppoeMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

-- | Set the value of the “@parent@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingPppoe [ #parent 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingPppoeParent :: (MonadIO m, IsSettingPppoe o) => o -> T.Text -> m ()
setSettingPppoeParent :: forall (m :: * -> *) o.
(MonadIO m, IsSettingPppoe o) =>
o -> Text -> m ()
setSettingPppoeParent 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
"parent" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a t'GValueConstruct' with valid value for the “@parent@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingPppoeParent :: (IsSettingPppoe o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingPppoeParent :: forall o (m :: * -> *).
(IsSettingPppoe o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingPppoeParent 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
"parent" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@parent@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #parent
-- @
clearSettingPppoeParent :: (MonadIO m, IsSettingPppoe o) => o -> m ()
clearSettingPppoeParent :: forall (m :: * -> *) o. (MonadIO m, IsSettingPppoe o) => o -> m ()
clearSettingPppoeParent o
obj = 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
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"parent" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingPppoeParentPropertyInfo
instance AttrInfo SettingPppoeParentPropertyInfo where
    type AttrAllowedOps SettingPppoeParentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingPppoeParentPropertyInfo = IsSettingPppoe
    type AttrSetTypeConstraint SettingPppoeParentPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingPppoeParentPropertyInfo = (~) T.Text
    type AttrTransferType SettingPppoeParentPropertyInfo = T.Text
    type AttrGetType SettingPppoeParentPropertyInfo = T.Text
    type AttrLabel SettingPppoeParentPropertyInfo = "parent"
    type AttrOrigin SettingPppoeParentPropertyInfo = SettingPppoe
    attrGet = getSettingPppoeParent
    attrSet = setSettingPppoeParent
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingPppoeParent
    attrClear = clearSettingPppoeParent
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.parent"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#g:attr:parent"
        })
#endif

-- VVV Prop "password"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- 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' settingPppoe #password
-- @
getSettingPppoePassword :: (MonadIO m, IsSettingPppoe o) => o -> m T.Text
getSettingPppoePassword :: forall (m :: * -> *) o.
(MonadIO m, IsSettingPppoe o) =>
o -> m Text
getSettingPppoePassword 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
"getSettingPppoePassword" (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"

-- | Set 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.set' settingPppoe [ #password 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingPppoePassword :: (MonadIO m, IsSettingPppoe o) => o -> T.Text -> m ()
setSettingPppoePassword :: forall (m :: * -> *) o.
(MonadIO m, IsSettingPppoe o) =>
o -> Text -> m ()
setSettingPppoePassword 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
"password" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a t'GValueConstruct' with valid value for the “@password@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingPppoePassword :: (IsSettingPppoe o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingPppoePassword :: forall o (m :: * -> *).
(IsSettingPppoe o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingPppoePassword 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
"password" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@password@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #password
-- @
clearSettingPppoePassword :: (MonadIO m, IsSettingPppoe o) => o -> m ()
clearSettingPppoePassword :: forall (m :: * -> *) o. (MonadIO m, IsSettingPppoe o) => o -> m ()
clearSettingPppoePassword o
obj = 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
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"password" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingPppoePasswordPropertyInfo
instance AttrInfo SettingPppoePasswordPropertyInfo where
    type AttrAllowedOps SettingPppoePasswordPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingPppoePasswordPropertyInfo = IsSettingPppoe
    type AttrSetTypeConstraint SettingPppoePasswordPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingPppoePasswordPropertyInfo = (~) T.Text
    type AttrTransferType SettingPppoePasswordPropertyInfo = T.Text
    type AttrGetType SettingPppoePasswordPropertyInfo = T.Text
    type AttrLabel SettingPppoePasswordPropertyInfo = "password"
    type AttrOrigin SettingPppoePasswordPropertyInfo = SettingPppoe
    attrGet = getSettingPppoePassword
    attrSet = setSettingPppoePassword
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingPppoePassword
    attrClear = clearSettingPppoePassword
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.password"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#g:attr:password"
        })
#endif

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

-- | Get the value of the “@password-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingPppoe #passwordFlags
-- @
getSettingPppoePasswordFlags :: (MonadIO m, IsSettingPppoe o) => o -> m [NM.Flags.SettingSecretFlags]
getSettingPppoePasswordFlags :: forall (m :: * -> *) o.
(MonadIO m, IsSettingPppoe o) =>
o -> m [SettingSecretFlags]
getSettingPppoePasswordFlags o
obj = IO [SettingSecretFlags] -> m [SettingSecretFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [SettingSecretFlags] -> m [SettingSecretFlags])
-> IO [SettingSecretFlags] -> m [SettingSecretFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [SettingSecretFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"password-flags"

-- | Set the value of the “@password-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingPppoe [ #passwordFlags 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingPppoePasswordFlags :: (MonadIO m, IsSettingPppoe o) => o -> [NM.Flags.SettingSecretFlags] -> m ()
setSettingPppoePasswordFlags :: forall (m :: * -> *) o.
(MonadIO m, IsSettingPppoe o) =>
o -> [SettingSecretFlags] -> m ()
setSettingPppoePasswordFlags o
obj [SettingSecretFlags]
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 -> [SettingSecretFlags] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"password-flags" [SettingSecretFlags]
val

-- | Construct a t'GValueConstruct' with valid value for the “@password-flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingPppoePasswordFlags :: (IsSettingPppoe o, MIO.MonadIO m) => [NM.Flags.SettingSecretFlags] -> m (GValueConstruct o)
constructSettingPppoePasswordFlags :: forall o (m :: * -> *).
(IsSettingPppoe o, MonadIO m) =>
[SettingSecretFlags] -> m (GValueConstruct o)
constructSettingPppoePasswordFlags [SettingSecretFlags]
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 -> [SettingSecretFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"password-flags" [SettingSecretFlags]
val

#if defined(ENABLE_OVERLOADING)
data SettingPppoePasswordFlagsPropertyInfo
instance AttrInfo SettingPppoePasswordFlagsPropertyInfo where
    type AttrAllowedOps SettingPppoePasswordFlagsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingPppoePasswordFlagsPropertyInfo = IsSettingPppoe
    type AttrSetTypeConstraint SettingPppoePasswordFlagsPropertyInfo = (~) [NM.Flags.SettingSecretFlags]
    type AttrTransferTypeConstraint SettingPppoePasswordFlagsPropertyInfo = (~) [NM.Flags.SettingSecretFlags]
    type AttrTransferType SettingPppoePasswordFlagsPropertyInfo = [NM.Flags.SettingSecretFlags]
    type AttrGetType SettingPppoePasswordFlagsPropertyInfo = [NM.Flags.SettingSecretFlags]
    type AttrLabel SettingPppoePasswordFlagsPropertyInfo = "password-flags"
    type AttrOrigin SettingPppoePasswordFlagsPropertyInfo = SettingPppoe
    attrGet = getSettingPppoePasswordFlags
    attrSet = setSettingPppoePasswordFlags
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingPppoePasswordFlags
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.passwordFlags"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#g:attr:passwordFlags"
        })
#endif

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

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

-- | Set the value of the “@service@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingPppoe [ #service 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingPppoeService :: (MonadIO m, IsSettingPppoe o) => o -> T.Text -> m ()
setSettingPppoeService :: forall (m :: * -> *) o.
(MonadIO m, IsSettingPppoe o) =>
o -> Text -> m ()
setSettingPppoeService 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
"service" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a t'GValueConstruct' with valid value for the “@service@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingPppoeService :: (IsSettingPppoe o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingPppoeService :: forall o (m :: * -> *).
(IsSettingPppoe o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingPppoeService 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
"service" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@service@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #service
-- @
clearSettingPppoeService :: (MonadIO m, IsSettingPppoe o) => o -> m ()
clearSettingPppoeService :: forall (m :: * -> *) o. (MonadIO m, IsSettingPppoe o) => o -> m ()
clearSettingPppoeService o
obj = 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
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"service" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingPppoeServicePropertyInfo
instance AttrInfo SettingPppoeServicePropertyInfo where
    type AttrAllowedOps SettingPppoeServicePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingPppoeServicePropertyInfo = IsSettingPppoe
    type AttrSetTypeConstraint SettingPppoeServicePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingPppoeServicePropertyInfo = (~) T.Text
    type AttrTransferType SettingPppoeServicePropertyInfo = T.Text
    type AttrGetType SettingPppoeServicePropertyInfo = T.Text
    type AttrLabel SettingPppoeServicePropertyInfo = "service"
    type AttrOrigin SettingPppoeServicePropertyInfo = SettingPppoe
    attrGet = getSettingPppoeService
    attrSet = setSettingPppoeService
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingPppoeService
    attrClear = clearSettingPppoeService
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.service"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#g:attr:service"
        })
#endif

-- VVV Prop "username"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- 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' settingPppoe #username
-- @
getSettingPppoeUsername :: (MonadIO m, IsSettingPppoe o) => o -> m T.Text
getSettingPppoeUsername :: forall (m :: * -> *) o.
(MonadIO m, IsSettingPppoe o) =>
o -> m Text
getSettingPppoeUsername 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
"getSettingPppoeUsername" (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"

-- | Set 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.set' settingPppoe [ #username 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingPppoeUsername :: (MonadIO m, IsSettingPppoe o) => o -> T.Text -> m ()
setSettingPppoeUsername :: forall (m :: * -> *) o.
(MonadIO m, IsSettingPppoe o) =>
o -> Text -> m ()
setSettingPppoeUsername 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
"username" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a t'GValueConstruct' with valid value for the “@username@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingPppoeUsername :: (IsSettingPppoe o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingPppoeUsername :: forall o (m :: * -> *).
(IsSettingPppoe o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingPppoeUsername 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
"username" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@username@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #username
-- @
clearSettingPppoeUsername :: (MonadIO m, IsSettingPppoe o) => o -> m ()
clearSettingPppoeUsername :: forall (m :: * -> *) o. (MonadIO m, IsSettingPppoe o) => o -> m ()
clearSettingPppoeUsername o
obj = 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
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"username" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingPppoeUsernamePropertyInfo
instance AttrInfo SettingPppoeUsernamePropertyInfo where
    type AttrAllowedOps SettingPppoeUsernamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingPppoeUsernamePropertyInfo = IsSettingPppoe
    type AttrSetTypeConstraint SettingPppoeUsernamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingPppoeUsernamePropertyInfo = (~) T.Text
    type AttrTransferType SettingPppoeUsernamePropertyInfo = T.Text
    type AttrGetType SettingPppoeUsernamePropertyInfo = T.Text
    type AttrLabel SettingPppoeUsernamePropertyInfo = "username"
    type AttrOrigin SettingPppoeUsernamePropertyInfo = SettingPppoe
    attrGet = getSettingPppoeUsername
    attrSet = setSettingPppoeUsername
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingPppoeUsername
    attrClear = clearSettingPppoeUsername
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.username"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#g:attr:username"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingPppoe
type instance O.AttributeList SettingPppoe = SettingPppoeAttributeList
type SettingPppoeAttributeList = ('[ '("name", NM.Setting.SettingNamePropertyInfo), '("parent", SettingPppoeParentPropertyInfo), '("password", SettingPppoePasswordPropertyInfo), '("passwordFlags", SettingPppoePasswordFlagsPropertyInfo), '("service", SettingPppoeServicePropertyInfo), '("username", SettingPppoeUsernamePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingPppoeParent :: AttrLabelProxy "parent"
settingPppoeParent = AttrLabelProxy

settingPppoePassword :: AttrLabelProxy "password"
settingPppoePassword = AttrLabelProxy

settingPppoePasswordFlags :: AttrLabelProxy "passwordFlags"
settingPppoePasswordFlags = AttrLabelProxy

settingPppoeService :: AttrLabelProxy "service"
settingPppoeService = AttrLabelProxy

settingPppoeUsername :: AttrLabelProxy "username"
settingPppoeUsername = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SettingPppoe = SettingPppoeSignalList
type SettingPppoeSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method SettingPppoe::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "NM" , name = "SettingPppoe" })
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_pppoe_new" nm_setting_pppoe_new :: 
    IO (Ptr SettingPppoe)

-- | Creates a new t'GI.NM.Objects.SettingPppoe.SettingPppoe' object with default values.
settingPppoeNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m SettingPppoe
    -- ^ __Returns:__ the new empty t'GI.NM.Objects.SettingPppoe.SettingPppoe' object
settingPppoeNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m SettingPppoe
settingPppoeNew  = IO SettingPppoe -> m SettingPppoe
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingPppoe -> m SettingPppoe)
-> IO SettingPppoe -> m SettingPppoe
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingPppoe
result <- IO (Ptr SettingPppoe)
nm_setting_pppoe_new
    Text -> Ptr SettingPppoe -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingPppoeNew" Ptr SettingPppoe
result
    SettingPppoe
result' <- ((ManagedPtr SettingPppoe -> SettingPppoe)
-> Ptr SettingPppoe -> IO SettingPppoe
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SettingPppoe -> SettingPppoe
SettingPppoe) Ptr SettingPppoe
result
    SettingPppoe -> IO SettingPppoe
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SettingPppoe
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method SettingPppoe::get_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingPppoe" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingPppoe"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_pppoe_get_parent" nm_setting_pppoe_get_parent :: 
    Ptr SettingPppoe ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingPppoe"})
    IO CString

-- | /No description available in the introspection data./
-- 
-- /Since: 1.10/
settingPppoeGetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingPppoe a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingPppoe.SettingPppoe'
    -> m T.Text
    -- ^ __Returns:__ the [SettingPppoe:parent]("GI.NM.Objects.SettingPppoe#g:attr:parent") property of the setting
settingPppoeGetParent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingPppoe a) =>
a -> m Text
settingPppoeGetParent a
setting = 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 SettingPppoe
setting' <- a -> IO (Ptr SettingPppoe)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingPppoe -> IO CString
nm_setting_pppoe_get_parent Ptr SettingPppoe
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingPppoeGetParent" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SettingPppoeGetParentMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingPppoe a) => O.OverloadedMethod SettingPppoeGetParentMethodInfo a signature where
    overloadedMethod = settingPppoeGetParent

instance O.OverloadedMethodInfo SettingPppoeGetParentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.settingPppoeGetParent",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#v:settingPppoeGetParent"
        })


#endif

-- method SettingPppoe::get_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingPppoe" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingPppoe"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_pppoe_get_password" nm_setting_pppoe_get_password :: 
    Ptr SettingPppoe ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingPppoe"})
    IO CString

-- | /No description available in the introspection data./
settingPppoeGetPassword ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingPppoe a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingPppoe.SettingPppoe'
    -> m T.Text
    -- ^ __Returns:__ the [SettingPppoe:password]("GI.NM.Objects.SettingPppoe#g:attr:password") property of the setting
settingPppoeGetPassword :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingPppoe a) =>
a -> m Text
settingPppoeGetPassword a
setting = 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 SettingPppoe
setting' <- a -> IO (Ptr SettingPppoe)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingPppoe -> IO CString
nm_setting_pppoe_get_password Ptr SettingPppoe
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingPppoeGetPassword" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SettingPppoeGetPasswordMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingPppoe a) => O.OverloadedMethod SettingPppoeGetPasswordMethodInfo a signature where
    overloadedMethod = settingPppoeGetPassword

instance O.OverloadedMethodInfo SettingPppoeGetPasswordMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.settingPppoeGetPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#v:settingPppoeGetPassword"
        })


#endif

-- method SettingPppoe::get_password_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingPppoe" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingPppoe"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "NM" , name = "SettingSecretFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_pppoe_get_password_flags" nm_setting_pppoe_get_password_flags :: 
    Ptr SettingPppoe ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingPppoe"})
    IO CUInt

-- | /No description available in the introspection data./
settingPppoeGetPasswordFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingPppoe a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingPppoe.SettingPppoe'
    -> m [NM.Flags.SettingSecretFlags]
    -- ^ __Returns:__ the t'GI.NM.Flags.SettingSecretFlags' pertaining to the [SettingPppoe:password]("GI.NM.Objects.SettingPppoe#g:attr:password")
settingPppoeGetPasswordFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingPppoe a) =>
a -> m [SettingSecretFlags]
settingPppoeGetPasswordFlags a
setting = IO [SettingSecretFlags] -> m [SettingSecretFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [SettingSecretFlags] -> m [SettingSecretFlags])
-> IO [SettingSecretFlags] -> m [SettingSecretFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingPppoe
setting' <- a -> IO (Ptr SettingPppoe)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CUInt
result <- Ptr SettingPppoe -> IO CUInt
nm_setting_pppoe_get_password_flags Ptr SettingPppoe
setting'
    let result' :: [SettingSecretFlags]
result' = CUInt -> [SettingSecretFlags]
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
setting
    [SettingSecretFlags] -> IO [SettingSecretFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [SettingSecretFlags]
result'

#if defined(ENABLE_OVERLOADING)
data SettingPppoeGetPasswordFlagsMethodInfo
instance (signature ~ (m [NM.Flags.SettingSecretFlags]), MonadIO m, IsSettingPppoe a) => O.OverloadedMethod SettingPppoeGetPasswordFlagsMethodInfo a signature where
    overloadedMethod = settingPppoeGetPasswordFlags

instance O.OverloadedMethodInfo SettingPppoeGetPasswordFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.settingPppoeGetPasswordFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#v:settingPppoeGetPasswordFlags"
        })


#endif

-- method SettingPppoe::get_service
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingPppoe" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingPppoe"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_pppoe_get_service" nm_setting_pppoe_get_service :: 
    Ptr SettingPppoe ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingPppoe"})
    IO CString

-- | /No description available in the introspection data./
settingPppoeGetService ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingPppoe a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingPppoe.SettingPppoe'
    -> m T.Text
    -- ^ __Returns:__ the [SettingPppoe:service]("GI.NM.Objects.SettingPppoe#g:attr:service") property of the setting
settingPppoeGetService :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingPppoe a) =>
a -> m Text
settingPppoeGetService a
setting = 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 SettingPppoe
setting' <- a -> IO (Ptr SettingPppoe)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingPppoe -> IO CString
nm_setting_pppoe_get_service Ptr SettingPppoe
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingPppoeGetService" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SettingPppoeGetServiceMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingPppoe a) => O.OverloadedMethod SettingPppoeGetServiceMethodInfo a signature where
    overloadedMethod = settingPppoeGetService

instance O.OverloadedMethodInfo SettingPppoeGetServiceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.settingPppoeGetService",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#v:settingPppoeGetService"
        })


#endif

-- method SettingPppoe::get_username
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingPppoe" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingPppoe"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_pppoe_get_username" nm_setting_pppoe_get_username :: 
    Ptr SettingPppoe ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingPppoe"})
    IO CString

-- | /No description available in the introspection data./
settingPppoeGetUsername ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingPppoe a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingPppoe.SettingPppoe'
    -> m T.Text
    -- ^ __Returns:__ the [SettingPppoe:username]("GI.NM.Objects.SettingPppoe#g:attr:username") property of the setting
settingPppoeGetUsername :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingPppoe a) =>
a -> m Text
settingPppoeGetUsername a
setting = 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 SettingPppoe
setting' <- a -> IO (Ptr SettingPppoe)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingPppoe -> IO CString
nm_setting_pppoe_get_username Ptr SettingPppoe
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingPppoeGetUsername" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SettingPppoeGetUsernameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingPppoe a) => O.OverloadedMethod SettingPppoeGetUsernameMethodInfo a signature where
    overloadedMethod = settingPppoeGetUsername

instance O.OverloadedMethodInfo SettingPppoeGetUsernameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingPppoe.settingPppoeGetUsername",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingPppoe.html#v:settingPppoeGetUsername"
        })


#endif