{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.NM.Objects.Setting
    ( 
#if defined(ENABLE_OVERLOADING)
    SettingDiffMethodInfo                   ,
#endif

-- * Exported types
    Setting(..)                             ,
    IsSetting                               ,
    toSetting                               ,


 -- * 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"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSecretFlags]("GI.NM.Objects.Setting#g:method:getSecretFlags").
-- 
-- ==== 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)
    ResolveSettingMethod                    ,
#endif

-- ** compare #method:compare#

#if defined(ENABLE_OVERLOADING)
    SettingCompareMethodInfo                ,
#endif
    settingCompare                          ,


-- ** duplicate #method:duplicate#

#if defined(ENABLE_OVERLOADING)
    SettingDuplicateMethodInfo              ,
#endif
    settingDuplicate                        ,


-- ** enumerateValues #method:enumerateValues#

#if defined(ENABLE_OVERLOADING)
    SettingEnumerateValuesMethodInfo        ,
#endif
    settingEnumerateValues                  ,


-- ** getDbusPropertyType #method:getDbusPropertyType#

#if defined(ENABLE_OVERLOADING)
    SettingGetDbusPropertyTypeMethodInfo    ,
#endif
    settingGetDbusPropertyType              ,


-- ** getEnumPropertyType #method:getEnumPropertyType#

    settingGetEnumPropertyType              ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    SettingGetNameMethodInfo                ,
#endif
    settingGetName                          ,


-- ** getSecretFlags #method:getSecretFlags#

#if defined(ENABLE_OVERLOADING)
    SettingGetSecretFlagsMethodInfo         ,
#endif
    settingGetSecretFlags                   ,


-- ** lookupType #method:lookupType#

    settingLookupType                       ,


-- ** optionClearByName #method:optionClearByName#

#if defined(ENABLE_OVERLOADING)
    SettingOptionClearByNameMethodInfo      ,
#endif
    settingOptionClearByName                ,


-- ** optionGet #method:optionGet#

#if defined(ENABLE_OVERLOADING)
    SettingOptionGetMethodInfo              ,
#endif
    settingOptionGet                        ,


-- ** optionGetAllNames #method:optionGetAllNames#

#if defined(ENABLE_OVERLOADING)
    SettingOptionGetAllNamesMethodInfo      ,
#endif
    settingOptionGetAllNames                ,


-- ** optionGetBoolean #method:optionGetBoolean#

#if defined(ENABLE_OVERLOADING)
    SettingOptionGetBooleanMethodInfo       ,
#endif
    settingOptionGetBoolean                 ,


-- ** optionGetUint32 #method:optionGetUint32#

#if defined(ENABLE_OVERLOADING)
    SettingOptionGetUint32MethodInfo        ,
#endif
    settingOptionGetUint32                  ,


-- ** optionSet #method:optionSet#

#if defined(ENABLE_OVERLOADING)
    SettingOptionSetMethodInfo              ,
#endif
    settingOptionSet                        ,


-- ** optionSetBoolean #method:optionSetBoolean#

#if defined(ENABLE_OVERLOADING)
    SettingOptionSetBooleanMethodInfo       ,
#endif
    settingOptionSetBoolean                 ,


-- ** optionSetUint32 #method:optionSetUint32#

#if defined(ENABLE_OVERLOADING)
    SettingOptionSetUint32MethodInfo        ,
#endif
    settingOptionSetUint32                  ,


-- ** setSecretFlags #method:setSecretFlags#

#if defined(ENABLE_OVERLOADING)
    SettingSetSecretFlagsMethodInfo         ,
#endif
    settingSetSecretFlags                   ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    SettingToStringMethodInfo               ,
#endif
    settingToString                         ,


-- ** verify #method:verify#

#if defined(ENABLE_OVERLOADING)
    SettingVerifyMethodInfo                 ,
#endif
    settingVerify                           ,


-- ** verifySecrets #method:verifySecrets#

#if defined(ENABLE_OVERLOADING)
    SettingVerifySecretsMethodInfo          ,
#endif
    settingVerifySecrets                    ,




 -- * Properties


-- ** name #attr:name#
-- | The setting\'s name, which uniquely identifies the setting within the
-- connection.  Each setting type has a name unique to that type, for
-- example \"ppp\" or \"802-11-wireless\" or \"802-3-ethernet\".

#if defined(ENABLE_OVERLOADING)
    SettingNamePropertyInfo                 ,
#endif
    getSettingName                          ,
#if defined(ENABLE_OVERLOADING)
    settingName                             ,
#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.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.SettingPppoe as NM.SettingPppoe
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.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

#endif

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

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

foreign import ccall "nm_setting_get_type"
    c_nm_setting_get_type :: IO B.Types.GType

instance B.Types.TypedObject Setting where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_get_type

instance B.Types.GObject Setting

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

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

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

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

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

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

#endif

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

#endif

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

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

#if defined(ENABLE_OVERLOADING)
data SettingNamePropertyInfo
instance AttrInfo SettingNamePropertyInfo where
    type AttrAllowedOps SettingNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingNamePropertyInfo = IsSetting
    type AttrSetTypeConstraint SettingNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint SettingNamePropertyInfo = (~) ()
    type AttrTransferType SettingNamePropertyInfo = ()
    type AttrGetType SettingNamePropertyInfo = T.Text
    type AttrLabel SettingNamePropertyInfo = "name"
    type AttrOrigin SettingNamePropertyInfo = Setting
    attrGet = getSettingName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.Setting.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-Setting.html#g:attr:name"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Setting
type instance O.AttributeList Setting = SettingAttributeList
type SettingAttributeList = ('[ '("name", SettingNamePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingName :: AttrLabelProxy "name"
settingName = AttrLabelProxy

#endif

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

#endif

-- method Setting::compare
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a second #NMSetting to compare with the first"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingCompareFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "compare flags, e.g. %NM_SETTING_COMPARE_FLAG_EXACT"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_compare" nm_setting_compare :: 
    Ptr Setting ->                          -- a : TInterface (Name {namespace = "NM", name = "Setting"})
    Ptr Setting ->                          -- b : TInterface (Name {namespace = "NM", name = "Setting"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "NM", name = "SettingCompareFlags"})
    IO CInt

-- | Compares two t'GI.NM.Objects.Setting.Setting' objects for similarity, with comparison behavior
-- modified by a set of flags.  See the documentation for t'GI.NM.Enums.SettingCompareFlags'
-- for a description of each flag\'s behavior.
settingCompare ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a, IsSetting b) =>
    a
    -- ^ /@a@/: a t'GI.NM.Objects.Setting.Setting'
    -> b
    -- ^ /@b@/: a second t'GI.NM.Objects.Setting.Setting' to compare with the first
    -> NM.Enums.SettingCompareFlags
    -- ^ /@flags@/: compare flags, e.g. 'GI.NM.Enums.SettingCompareFlagsExact'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the comparison succeeds, 'P.False' if it does not
settingCompare :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSetting a, IsSetting b) =>
a -> b -> SettingCompareFlags -> m Bool
settingCompare a
a b
b SettingCompareFlags
flags = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
a' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
a
    Ptr Setting
b' <- b -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
b
    let flags' :: CUInt
flags' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (SettingCompareFlags -> Int) -> SettingCompareFlags -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SettingCompareFlags -> Int
forall a. Enum a => a -> Int
fromEnum) SettingCompareFlags
flags
    CInt
result <- Ptr Setting -> Ptr Setting -> CUInt -> IO CInt
nm_setting_compare Ptr Setting
a' Ptr Setting
b' CUInt
flags'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
a
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
b
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingCompareMethodInfo
instance (signature ~ (b -> NM.Enums.SettingCompareFlags -> m Bool), MonadIO m, IsSetting a, IsSetting b) => O.OverloadedMethod SettingCompareMethodInfo a signature where
    overloadedMethod = settingCompare

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


#endif

-- XXX Could not generate method Setting::diff
-- Not implemented: GHashTable element of type TBasicType TUInt32 unsupported.
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data SettingDiffMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "diff" Setting) => O.OverloadedMethod SettingDiffMethodInfo o p where
    overloadedMethod = undefined

instance (o ~ O.UnsupportedMethodError "diff" Setting) => O.OverloadedMethodInfo SettingDiffMethodInfo o where
    overloadedMethodInfo = undefined

#endif

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

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

-- | Duplicates a t'GI.NM.Objects.Setting.Setting'.
settingDuplicate ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting' to duplicate
    -> m Setting
    -- ^ __Returns:__ a new t'GI.NM.Objects.Setting.Setting' containing the same properties and values as the
    -- source t'GI.NM.Objects.Setting.Setting'
settingDuplicate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> m Setting
settingDuplicate a
setting = IO Setting -> m Setting
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Setting -> m Setting) -> IO Setting -> m Setting
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Ptr Setting
result <- Ptr Setting -> IO (Ptr Setting)
nm_setting_duplicate Ptr Setting
setting'
    Text -> Ptr Setting -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingDuplicate" Ptr Setting
result
    Setting
result' <- ((ManagedPtr Setting -> Setting) -> Ptr Setting -> IO Setting
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Setting -> Setting
Setting) Ptr Setting
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Setting -> IO Setting
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Setting
result'

#if defined(ENABLE_OVERLOADING)
data SettingDuplicateMethodInfo
instance (signature ~ (m Setting), MonadIO m, IsSetting a) => O.OverloadedMethod SettingDuplicateMethodInfo a signature where
    overloadedMethod = settingDuplicate

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


#endif

-- method Setting::enumerate_values
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "func"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingValueIterFn" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "user-supplied function called for each property of the setting"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data passed to @func at each invocation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_enumerate_values" nm_setting_enumerate_values :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    FunPtr NM.Callbacks.C_SettingValueIterFn -> -- func : TInterface (Name {namespace = "NM", name = "SettingValueIterFn"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Iterates over each property of the t'GI.NM.Objects.Setting.Setting' object, calling the supplied
-- user function for each property.
settingEnumerateValues ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> NM.Callbacks.SettingValueIterFn
    -- ^ /@func@/: user-supplied function called for each property of the setting
    -> m ()
settingEnumerateValues :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> SettingValueIterFn -> m ()
settingEnumerateValues a
setting SettingValueIterFn
func = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    FunPtr C_SettingValueIterFn
func' <- C_SettingValueIterFn -> IO (FunPtr C_SettingValueIterFn)
NM.Callbacks.mk_SettingValueIterFn (Maybe (Ptr (FunPtr C_SettingValueIterFn))
-> SettingValueIterFn_WithClosures -> C_SettingValueIterFn
NM.Callbacks.wrap_SettingValueIterFn Maybe (Ptr (FunPtr C_SettingValueIterFn))
forall a. Maybe a
Nothing (SettingValueIterFn -> SettingValueIterFn_WithClosures
NM.Callbacks.drop_closures_SettingValueIterFn SettingValueIterFn
func))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Setting -> FunPtr C_SettingValueIterFn -> Ptr () -> IO ()
nm_setting_enumerate_values Ptr Setting
setting' FunPtr C_SettingValueIterFn
func' Ptr ()
forall a. Ptr a
userData
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_SettingValueIterFn -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_SettingValueIterFn
func'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingEnumerateValuesMethodInfo
instance (signature ~ (NM.Callbacks.SettingValueIterFn -> m ()), MonadIO m, IsSetting a) => O.OverloadedMethod SettingEnumerateValuesMethodInfo a signature where
    overloadedMethod = settingEnumerateValues

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


#endif

-- method Setting::get_dbus_property_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the property of @setting to get the type of"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GLib" , name = "VariantType" })
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_get_dbus_property_type" nm_setting_get_dbus_property_type :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- property_name : TBasicType TUTF8
    IO (Ptr GLib.VariantType.VariantType)

-- | Gets the D-Bus marshalling type of a property. /@propertyName@/ is a D-Bus
-- property name, which may not necessarily be a t'GI.GObject.Objects.Object.Object' property.
settingGetDbusPropertyType ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: an t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -- ^ /@propertyName@/: the property of /@setting@/ to get the type of
    -> m GLib.VariantType.VariantType
    -- ^ __Returns:__ the D-Bus marshalling type of /@property@/ on /@setting@/.
settingGetDbusPropertyType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> m VariantType
settingGetDbusPropertyType a
setting Text
propertyName = IO VariantType -> m VariantType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VariantType -> m VariantType)
-> IO VariantType -> m VariantType
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    Ptr VariantType
result <- Ptr Setting -> CString -> IO (Ptr VariantType)
nm_setting_get_dbus_property_type Ptr Setting
setting' CString
propertyName'
    Text -> Ptr VariantType -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingGetDbusPropertyType" Ptr VariantType
result
    VariantType
result' <- ((ManagedPtr VariantType -> VariantType)
-> Ptr VariantType -> IO VariantType
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr VariantType -> VariantType
GLib.VariantType.VariantType) Ptr VariantType
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    VariantType -> IO VariantType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return VariantType
result'

#if defined(ENABLE_OVERLOADING)
data SettingGetDbusPropertyTypeMethodInfo
instance (signature ~ (T.Text -> m GLib.VariantType.VariantType), MonadIO m, IsSetting a) => O.OverloadedMethod SettingGetDbusPropertyTypeMethodInfo a signature where
    overloadedMethod = settingGetDbusPropertyType

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


#endif

-- method Setting::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , 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_get_name" nm_setting_get_name :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    IO CString

-- | Returns the type name of the t'GI.NM.Objects.Setting.Setting' object
settingGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> m T.Text
    -- ^ __Returns:__ a string containing the type name of the t'GI.NM.Objects.Setting.Setting' object,
    -- like \'ppp\' or \'wireless\' or \'wired\'.
settingGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> m Text
settingGetName 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 Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr Setting -> IO CString
nm_setting_get_name Ptr Setting
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingGetName" 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 SettingGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSetting a) => O.OverloadedMethod SettingGetNameMethodInfo a signature where
    overloadedMethod = settingGetName

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


#endif

-- method Setting::get_secret_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "secret_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the secret key name to get flags for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_flags"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingSecretFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "on success, the #NMSettingSecretFlags for the secret"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "nm_setting_get_secret_flags" nm_setting_get_secret_flags :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- secret_name : TBasicType TUTF8
    CUInt ->                                -- out_flags : TInterface (Name {namespace = "NM", name = "SettingSecretFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | For a given secret, retrieves the t'GI.NM.Flags.SettingSecretFlags' describing how to
-- handle that secret.
settingGetSecretFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -- ^ /@secretName@/: the secret key name to get flags for
    -> [NM.Flags.SettingSecretFlags]
    -- ^ /@outFlags@/: on success, the t'GI.NM.Flags.SettingSecretFlags' for the secret
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
settingGetSecretFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> [SettingSecretFlags] -> m ()
settingGetSecretFlags a
setting Text
secretName [SettingSecretFlags]
outFlags = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
secretName' <- Text -> IO CString
textToCString Text
secretName
    let outFlags' :: CUInt
outFlags' = [SettingSecretFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SettingSecretFlags]
outFlags
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Setting -> CString -> CUInt -> Ptr (Ptr GError) -> IO CInt
nm_setting_get_secret_flags Ptr Setting
setting' CString
secretName' CUInt
outFlags'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
secretName'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
secretName'
     )

#if defined(ENABLE_OVERLOADING)
data SettingGetSecretFlagsMethodInfo
instance (signature ~ (T.Text -> [NM.Flags.SettingSecretFlags] -> m ()), MonadIO m, IsSetting a) => O.OverloadedMethod SettingGetSecretFlagsMethodInfo a signature where
    overloadedMethod = settingGetSecretFlags

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


#endif

-- method Setting::option_clear_by_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "predicate"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "UtilsPredicateStr" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the predicate for which names\n  should be clear.\n  If the predicate returns %TRUE for an option name, the option\n  gets removed. If %NULL, all options will be removed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_option_clear_by_name" nm_setting_option_clear_by_name :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    FunPtr NM.Callbacks.C_UtilsPredicateStr -> -- predicate : TInterface (Name {namespace = "NM", name = "UtilsPredicateStr"})
    IO ()

-- | /No description available in the introspection data./
-- 
-- /Since: 1.26/
settingOptionClearByName ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> Maybe (NM.Callbacks.UtilsPredicateStr)
    -- ^ /@predicate@/: the predicate for which names
    --   should be clear.
    --   If the predicate returns 'P.True' for an option name, the option
    --   gets removed. If 'P.Nothing', all options will be removed.
    -> m ()
settingOptionClearByName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Maybe UtilsPredicateStr -> m ()
settingOptionClearByName a
setting Maybe UtilsPredicateStr
predicate = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    FunPtr C_UtilsPredicateStr
maybePredicate <- case Maybe UtilsPredicateStr
predicate of
        Maybe UtilsPredicateStr
Nothing -> FunPtr C_UtilsPredicateStr -> IO (FunPtr C_UtilsPredicateStr)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_UtilsPredicateStr
forall a. FunPtr a
FP.nullFunPtr
        Just UtilsPredicateStr
jPredicate -> do
            FunPtr C_UtilsPredicateStr
jPredicate' <- C_UtilsPredicateStr -> IO (FunPtr C_UtilsPredicateStr)
NM.Callbacks.mk_UtilsPredicateStr (Maybe (Ptr (FunPtr C_UtilsPredicateStr))
-> UtilsPredicateStr -> C_UtilsPredicateStr
NM.Callbacks.wrap_UtilsPredicateStr Maybe (Ptr (FunPtr C_UtilsPredicateStr))
forall a. Maybe a
Nothing UtilsPredicateStr
jPredicate)
            FunPtr C_UtilsPredicateStr -> IO (FunPtr C_UtilsPredicateStr)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_UtilsPredicateStr
jPredicate'
    Ptr Setting -> FunPtr C_UtilsPredicateStr -> IO ()
nm_setting_option_clear_by_name Ptr Setting
setting' FunPtr C_UtilsPredicateStr
maybePredicate
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_UtilsPredicateStr -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_UtilsPredicateStr
maybePredicate
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingOptionClearByNameMethodInfo
instance (signature ~ (Maybe (NM.Callbacks.UtilsPredicateStr) -> m ()), MonadIO m, IsSetting a) => O.OverloadedMethod SettingOptionClearByNameMethodInfo a signature where
    overloadedMethod = settingOptionClearByName

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


#endif

-- method Setting::option_get
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "opt_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the option name to request."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_option_get" nm_setting_option_get :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- opt_name : TBasicType TUTF8
    IO (Ptr GVariant)

-- | /No description available in the introspection data./
-- 
-- /Since: 1.26/
settingOptionGet ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -- ^ /@optName@/: the option name to request.
    -> m GVariant
    -- ^ __Returns:__ the t'GVariant' or 'P.Nothing' if the option
    --   is not set.
settingOptionGet :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> m GVariant
settingOptionGet a
setting Text
optName = IO GVariant -> m GVariant
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
optName' <- Text -> IO CString
textToCString Text
optName
    Ptr GVariant
result <- Ptr Setting -> CString -> IO (Ptr GVariant)
nm_setting_option_get Ptr Setting
setting' CString
optName'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingOptionGet" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
optName'
    GVariant -> IO GVariant
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data SettingOptionGetMethodInfo
instance (signature ~ (T.Text -> m GVariant), MonadIO m, IsSetting a) => O.OverloadedMethod SettingOptionGetMethodInfo a signature where
    overloadedMethod = settingOptionGet

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


#endif

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

foreign import ccall "nm_setting_option_get_all_names" nm_setting_option_get_all_names :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    Ptr Word32 ->                           -- out_len : TBasicType TUInt
    IO (Ptr CString)

-- | Gives the name of all set options.
-- 
-- /Since: 1.26/
settingOptionGetAllNames ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> m ((Maybe [T.Text], Word32))
    -- ^ __Returns:__ 
    --   A 'P.Nothing' terminated array of key names. If no names are present, this returns
    --   'P.Nothing'. The returned array and the names are owned by @/NMSetting/@ and might be invalidated
    --   by the next operation.
settingOptionGetAllNames :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> m (Maybe [Text], Word32)
settingOptionGetAllNames a
setting = IO (Maybe [Text], Word32) -> m (Maybe [Text], Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Text], Word32) -> m (Maybe [Text], Word32))
-> IO (Maybe [Text], Word32) -> m (Maybe [Text], Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Ptr Word32
outLen <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr CString
result <- Ptr Setting -> Ptr Word32 -> IO (Ptr CString)
nm_setting_option_get_all_names Ptr Setting
setting' Ptr Word32
outLen
    Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
        [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    Word32
outLen' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
outLen
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
outLen
    (Maybe [Text], Word32) -> IO (Maybe [Text], Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [Text]
maybeResult, Word32
outLen')

#if defined(ENABLE_OVERLOADING)
data SettingOptionGetAllNamesMethodInfo
instance (signature ~ (m ((Maybe [T.Text], Word32))), MonadIO m, IsSetting a) => O.OverloadedMethod SettingOptionGetAllNamesMethodInfo a signature where
    overloadedMethod = settingOptionGetAllNames

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


#endif

-- method Setting::option_get_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "opt_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the option to get" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_value"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the optional output value.\n  If the option is unset, %FALSE will be returned."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_option_get_boolean" nm_setting_option_get_boolean :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- opt_name : TBasicType TUTF8
    Ptr CInt ->                             -- out_value : TBasicType TBoolean
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.26/
settingOptionGetBoolean ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -- ^ /@optName@/: the option to get
    -> m ((Bool, Bool))
    -- ^ __Returns:__ 'P.True' if /@optName@/ is set to a boolean variant.
settingOptionGetBoolean :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> m (Bool, Bool)
settingOptionGetBoolean a
setting Text
optName = IO (Bool, Bool) -> m (Bool, Bool)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Bool) -> m (Bool, Bool))
-> IO (Bool, Bool) -> m (Bool, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
optName' <- Text -> IO CString
textToCString Text
optName
    Ptr CInt
outValue <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    CInt
result <- Ptr Setting -> CString -> Ptr CInt -> IO CInt
nm_setting_option_get_boolean Ptr Setting
setting' CString
optName' Ptr CInt
outValue
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    CInt
outValue' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
outValue
    let outValue'' :: Bool
outValue'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
outValue'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
optName'
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
outValue
    (Bool, Bool) -> IO (Bool, Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Bool
outValue'')

#if defined(ENABLE_OVERLOADING)
data SettingOptionGetBooleanMethodInfo
instance (signature ~ (T.Text -> m ((Bool, Bool))), MonadIO m, IsSetting a) => O.OverloadedMethod SettingOptionGetBooleanMethodInfo a signature where
    overloadedMethod = settingOptionGetBoolean

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


#endif

-- method Setting::option_get_uint32
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "opt_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the option to get" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_value"
--           , argType = TBasicType TUInt32
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the optional output value.\n  If the option is unset, 0 will be returned."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_option_get_uint32" nm_setting_option_get_uint32 :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- opt_name : TBasicType TUTF8
    Ptr Word32 ->                           -- out_value : TBasicType TUInt32
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.26/
settingOptionGetUint32 ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -- ^ /@optName@/: the option to get
    -> m ((Bool, Word32))
    -- ^ __Returns:__ 'P.True' if /@optName@/ is set to a uint32 variant.
settingOptionGetUint32 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> m (Bool, Word32)
settingOptionGetUint32 a
setting Text
optName = IO (Bool, Word32) -> m (Bool, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Word32) -> m (Bool, Word32))
-> IO (Bool, Word32) -> m (Bool, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
optName' <- Text -> IO CString
textToCString Text
optName
    Ptr Word32
outValue <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr Setting -> CString -> Ptr Word32 -> IO CInt
nm_setting_option_get_uint32 Ptr Setting
setting' CString
optName' Ptr Word32
outValue
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Word32
outValue' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
outValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
optName'
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
outValue
    (Bool, Word32) -> IO (Bool, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Word32
outValue')

#if defined(ENABLE_OVERLOADING)
data SettingOptionGetUint32MethodInfo
instance (signature ~ (T.Text -> m ((Bool, Word32))), MonadIO m, IsSetting a) => O.OverloadedMethod SettingOptionGetUint32MethodInfo a signature where
    overloadedMethod = settingOptionGetUint32

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


#endif

-- method Setting::option_set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "opt_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the option name to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "variant"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the variant to set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_option_set" nm_setting_option_set :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- opt_name : TBasicType TUTF8
    Ptr GVariant ->                         -- variant : TVariant
    IO ()

-- | If /@variant@/ is 'P.Nothing', this clears the option if it is set.
-- Otherwise, /@variant@/ is set as the option. If /@variant@/ is
-- a floating reference, it will be consumed.
-- 
-- Note that not all setting types support options. It is a bug
-- setting a variant to a setting that doesn\'t support it.
-- Currently, only t'GI.NM.Objects.SettingEthtool.SettingEthtool' supports it.
-- 
-- /Since: 1.26/
settingOptionSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -- ^ /@optName@/: the option name to set
    -> Maybe (GVariant)
    -- ^ /@variant@/: the variant to set.
    -> m ()
settingOptionSet :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> Maybe GVariant -> m ()
settingOptionSet a
setting Text
optName Maybe GVariant
variant = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
optName' <- Text -> IO CString
textToCString Text
optName
    Ptr GVariant
maybeVariant <- case Maybe GVariant
variant of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
FP.nullPtr
        Just GVariant
jVariant -> do
            Ptr GVariant
jVariant' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jVariant
            Ptr GVariant -> IO (Ptr GVariant)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jVariant'
    Ptr Setting -> CString -> Ptr GVariant -> IO ()
nm_setting_option_set Ptr Setting
setting' CString
optName' Ptr GVariant
maybeVariant
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
variant GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
optName'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingOptionSetMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> m ()), MonadIO m, IsSetting a) => O.OverloadedMethod SettingOptionSetMethodInfo a signature where
    overloadedMethod = settingOptionSet

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


#endif

-- method Setting::option_set_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "opt_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_option_set_boolean" nm_setting_option_set_boolean :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- opt_name : TBasicType TUTF8
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()

-- | Like 'GI.NM.Objects.Setting.settingOptionSet' to set a boolean GVariant.
-- 
-- /Since: 1.26/
settingOptionSetBoolean ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -> Bool
    -- ^ /@value@/: the value to set.
    -> m ()
settingOptionSetBoolean :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> Bool -> m ()
settingOptionSetBoolean a
setting Text
optName Bool
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
optName' <- Text -> IO CString
textToCString Text
optName
    let value' :: CInt
value' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
value
    Ptr Setting -> CString -> CInt -> IO ()
nm_setting_option_set_boolean Ptr Setting
setting' CString
optName' CInt
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
optName'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingOptionSetBooleanMethodInfo
instance (signature ~ (T.Text -> Bool -> m ()), MonadIO m, IsSetting a) => O.OverloadedMethod SettingOptionSetBooleanMethodInfo a signature where
    overloadedMethod = settingOptionSetBoolean

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


#endif

-- method Setting::option_set_uint32
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "opt_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_option_set_uint32" nm_setting_option_set_uint32 :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- opt_name : TBasicType TUTF8
    Word32 ->                               -- value : TBasicType TUInt32
    IO ()

-- | Like 'GI.NM.Objects.Setting.settingOptionSet' to set a uint32 GVariant.
-- 
-- /Since: 1.26/
settingOptionSetUint32 ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -> Word32
    -- ^ /@value@/: the value to set.
    -> m ()
settingOptionSetUint32 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> Word32 -> m ()
settingOptionSetUint32 a
setting Text
optName Word32
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
optName' <- Text -> IO CString
textToCString Text
optName
    Ptr Setting -> CString -> Word32 -> IO ()
nm_setting_option_set_uint32 Ptr Setting
setting' CString
optName' Word32
value
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
optName'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingOptionSetUint32MethodInfo
instance (signature ~ (T.Text -> Word32 -> m ()), MonadIO m, IsSetting a) => O.OverloadedMethod SettingOptionSetUint32MethodInfo a signature where
    overloadedMethod = settingOptionSetUint32

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


#endif

-- method Setting::set_secret_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "secret_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the secret key name to set flags for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingSecretFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingSecretFlags for the secret"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "nm_setting_set_secret_flags" nm_setting_set_secret_flags :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    CString ->                              -- secret_name : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "NM", name = "SettingSecretFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | For a given secret, stores the t'GI.NM.Flags.SettingSecretFlags' describing how to
-- handle that secret.
settingSetSecretFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> T.Text
    -- ^ /@secretName@/: the secret key name to set flags for
    -> [NM.Flags.SettingSecretFlags]
    -- ^ /@flags@/: the t'GI.NM.Flags.SettingSecretFlags' for the secret
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
settingSetSecretFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> Text -> [SettingSecretFlags] -> m ()
settingSetSecretFlags a
setting Text
secretName [SettingSecretFlags]
flags = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
secretName' <- Text -> IO CString
textToCString Text
secretName
    let flags' :: CUInt
flags' = [SettingSecretFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SettingSecretFlags]
flags
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Setting -> CString -> CUInt -> Ptr (Ptr GError) -> IO CInt
nm_setting_set_secret_flags Ptr Setting
setting' CString
secretName' CUInt
flags'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
secretName'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
secretName'
     )

#if defined(ENABLE_OVERLOADING)
data SettingSetSecretFlagsMethodInfo
instance (signature ~ (T.Text -> [NM.Flags.SettingSecretFlags] -> m ()), MonadIO m, IsSetting a) => O.OverloadedMethod SettingSetSecretFlagsMethodInfo a signature where
    overloadedMethod = settingSetSecretFlags

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


#endif

-- method Setting::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting" , 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_to_string" nm_setting_to_string :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    IO CString

-- | Convert the setting (including secrets!) into a string. For debugging
-- purposes ONLY, should NOT be used for serialization of the setting,
-- or machine-parsed in any way. The output format is not guaranteed to
-- be stable and may change at any time.
settingToString ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting'
    -> m T.Text
    -- ^ __Returns:__ an allocated string containing a textual representation of the
    -- setting\'s properties and values, which the caller should
    -- free with 'GI.GLib.Functions.free'
settingToString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSetting a) =>
a -> m Text
settingToString 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 Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr Setting -> IO CString
nm_setting_to_string Ptr Setting
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingToString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem 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 SettingToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSetting a) => O.OverloadedMethod SettingToStringMethodInfo a signature where
    overloadedMethod = settingToString

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


#endif

-- method Setting::verify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting to verify"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "Connection" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #NMConnection that @setting came from, or\n  %NULL if @setting is being verified in isolation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "nm_setting_verify" nm_setting_verify :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    Ptr NM.Connection.Connection ->         -- connection : TInterface (Name {namespace = "NM", name = "Connection"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Validates the setting.  Each setting\'s properties have allowed values, and
-- some are dependent on other values (hence the need for /@connection@/).  The
-- returned t'GError' contains information about which property of the setting
-- failed validation, and in what way that property failed validation.
settingVerify ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a, NM.Connection.IsConnection b) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting' to verify
    -> Maybe (b)
    -- ^ /@connection@/: the t'GI.NM.Interfaces.Connection.Connection' that /@setting@/ came from, or
    --   'P.Nothing' if /@setting@/ is being verified in isolation.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
settingVerify :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSetting a, IsConnection b) =>
a -> Maybe b -> m ()
settingVerify a
setting Maybe b
connection = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Ptr Connection
maybeConnection <- case Maybe b
connection of
        Maybe b
Nothing -> Ptr Connection -> IO (Ptr Connection)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Connection
forall a. Ptr a
FP.nullPtr
        Just b
jConnection -> do
            Ptr Connection
jConnection' <- b -> IO (Ptr Connection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jConnection
            Ptr Connection -> IO (Ptr Connection)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Connection
jConnection'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Setting -> Ptr Connection -> Ptr (Ptr GError) -> IO CInt
nm_setting_verify Ptr Setting
setting' Ptr Connection
maybeConnection
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
connection b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data SettingVerifyMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsSetting a, NM.Connection.IsConnection b) => O.OverloadedMethod SettingVerifyMethodInfo a signature where
    overloadedMethod = settingVerify

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


#endif

-- method Setting::verify_secrets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType = TInterface Name { namespace = "NM" , name = "Setting" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSetting to verify secrets in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "Connection" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #NMConnection that @setting came from, or\n  %NULL if @setting is being verified in isolation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "nm_setting_verify_secrets" nm_setting_verify_secrets :: 
    Ptr Setting ->                          -- setting : TInterface (Name {namespace = "NM", name = "Setting"})
    Ptr NM.Connection.Connection ->         -- connection : TInterface (Name {namespace = "NM", name = "Connection"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Verifies the secrets in the setting.
-- The returned t'GError' contains information about which secret of the setting
-- failed validation, and in what way that secret failed validation.
-- The secret validation is done separately from main setting validation, because
-- in some cases connection failure is not desired just for the secrets.
-- 
-- /Since: 1.2/
settingVerifySecrets ::
    (B.CallStack.HasCallStack, MonadIO m, IsSetting a, NM.Connection.IsConnection b) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.Setting.Setting' to verify secrets in
    -> Maybe (b)
    -- ^ /@connection@/: the t'GI.NM.Interfaces.Connection.Connection' that /@setting@/ came from, or
    --   'P.Nothing' if /@setting@/ is being verified in isolation.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
settingVerifySecrets :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSetting a, IsConnection b) =>
a -> Maybe b -> m ()
settingVerifySecrets a
setting Maybe b
connection = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Setting
setting' <- a -> IO (Ptr Setting)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Ptr Connection
maybeConnection <- case Maybe b
connection of
        Maybe b
Nothing -> Ptr Connection -> IO (Ptr Connection)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Connection
forall a. Ptr a
FP.nullPtr
        Just b
jConnection -> do
            Ptr Connection
jConnection' <- b -> IO (Ptr Connection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jConnection
            Ptr Connection -> IO (Ptr Connection)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Connection
jConnection'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Setting -> Ptr Connection -> Ptr (Ptr GError) -> IO CInt
nm_setting_verify_secrets Ptr Setting
setting' Ptr Connection
maybeConnection
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
connection b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data SettingVerifySecretsMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsSetting a, NM.Connection.IsConnection b) => O.OverloadedMethod SettingVerifySecretsMethodInfo a signature where
    overloadedMethod = settingVerifySecrets

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


#endif

-- method Setting::get_enum_property_type
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "setting_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the GType of the NMSetting instance"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the property"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_get_enum_property_type" nm_setting_get_enum_property_type :: 
    CGType ->                               -- setting_type : TBasicType TGType
    CString ->                              -- property_name : TBasicType TUTF8
    IO CGType

-- | Get the type of the enum that defines the values that the property accepts. It is only
-- useful for properties configured to accept values from certain enum type, otherwise
-- it will return @/G_TYPE_INVALID/@. Note that flags (children of G_TYPE_FLAGS) are also
-- considered enums.
-- 
-- Note that the GObject property might be implemented as an integer, actually, and not
-- as enum. Find out what underlying type is used, checking the t'GI.GObject.Objects.ParamSpec.ParamSpec', before
-- setting the GObject property.
-- 
-- /Since: 1.46/
settingGetEnumPropertyType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GType
    -- ^ /@settingType@/: the GType of the NMSetting instance
    -> T.Text
    -- ^ /@propertyName@/: the name of the property
    -> m GType
    -- ^ __Returns:__ the enum\'s GType, or @/G_TYPE_INVALID/@ if the property is not of enum type
settingGetEnumPropertyType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GType -> Text -> m GType
settingGetEnumPropertyType GType
settingType Text
propertyName = IO GType -> m GType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    let settingType' :: CGType
settingType' = GType -> CGType
gtypeToCGType GType
settingType
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    CGType
result <- CGType -> CString -> IO CGType
nm_setting_get_enum_property_type CGType
settingType' CString
propertyName'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    GType -> IO GType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Setting::lookup_type
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a setting name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_lookup_type" nm_setting_lookup_type :: 
    CString ->                              -- name : TBasicType TUTF8
    IO CGType

-- | Returns the t'GType' of the setting\'s class for a given setting name.
settingLookupType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: a setting name
    -> m GType
    -- ^ __Returns:__ the t'GType' of the setting\'s class, or @/G_TYPE_INVALID/@ if
    --   /@name@/ is not recognized.
settingLookupType :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m GType
settingLookupType Text
name = IO GType -> m GType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    CGType
result <- CString -> IO CGType
nm_setting_lookup_type CString
name'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    GType -> IO GType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
#endif