{-# LANGUAGE TypeApplications #-}


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

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

module GI.NM.Objects.SettingIP4Config
    ( 

-- * Exported types
    SettingIP4Config(..)                    ,
    IsSettingIP4Config                      ,
    toSettingIP4Config                      ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addAddress]("GI.NM.Objects.SettingIPConfig#g:method:addAddress"), [addDhcpRejectServer]("GI.NM.Objects.SettingIPConfig#g:method:addDhcpRejectServer"), [addDns]("GI.NM.Objects.SettingIPConfig#g:method:addDns"), [addDnsOption]("GI.NM.Objects.SettingIPConfig#g:method:addDnsOption"), [addDnsSearch]("GI.NM.Objects.SettingIPConfig#g:method:addDnsSearch"), [addRoute]("GI.NM.Objects.SettingIPConfig#g:method:addRoute"), [addRoutingRule]("GI.NM.Objects.SettingIPConfig#g:method:addRoutingRule"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clearAddresses]("GI.NM.Objects.SettingIPConfig#g:method:clearAddresses"), [clearDhcpRejectServers]("GI.NM.Objects.SettingIPConfig#g:method:clearDhcpRejectServers"), [clearDns]("GI.NM.Objects.SettingIPConfig#g:method:clearDns"), [clearDnsOptions]("GI.NM.Objects.SettingIPConfig#g:method:clearDnsOptions"), [clearDnsSearches]("GI.NM.Objects.SettingIPConfig#g:method:clearDnsSearches"), [clearRoutes]("GI.NM.Objects.SettingIPConfig#g:method:clearRoutes"), [clearRoutingRules]("GI.NM.Objects.SettingIPConfig#g:method:clearRoutingRules"), [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"), [hasDnsOptions]("GI.NM.Objects.SettingIPConfig#g:method:hasDnsOptions"), [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"), [removeAddress]("GI.NM.Objects.SettingIPConfig#g:method:removeAddress"), [removeAddressByValue]("GI.NM.Objects.SettingIPConfig#g:method:removeAddressByValue"), [removeDhcpRejectServer]("GI.NM.Objects.SettingIPConfig#g:method:removeDhcpRejectServer"), [removeDns]("GI.NM.Objects.SettingIPConfig#g:method:removeDns"), [removeDnsByValue]("GI.NM.Objects.SettingIPConfig#g:method:removeDnsByValue"), [removeDnsOption]("GI.NM.Objects.SettingIPConfig#g:method:removeDnsOption"), [removeDnsOptionByValue]("GI.NM.Objects.SettingIPConfig#g:method:removeDnsOptionByValue"), [removeDnsSearch]("GI.NM.Objects.SettingIPConfig#g:method:removeDnsSearch"), [removeDnsSearchByValue]("GI.NM.Objects.SettingIPConfig#g:method:removeDnsSearchByValue"), [removeRoute]("GI.NM.Objects.SettingIPConfig#g:method:removeRoute"), [removeRouteByValue]("GI.NM.Objects.SettingIPConfig#g:method:removeRouteByValue"), [removeRoutingRule]("GI.NM.Objects.SettingIPConfig#g:method:removeRoutingRule"), [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
-- [getAddress]("GI.NM.Objects.SettingIPConfig#g:method:getAddress"), [getAutoRouteExtGw]("GI.NM.Objects.SettingIPConfig#g:method:getAutoRouteExtGw"), [getDadTimeout]("GI.NM.Objects.SettingIPConfig#g:method:getDadTimeout"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDbusPropertyType]("GI.NM.Objects.Setting#g:method:getDbusPropertyType"), [getDhcpClientId]("GI.NM.Objects.SettingIP4Config#g:method:getDhcpClientId"), [getDhcpDscp]("GI.NM.Objects.SettingIPConfig#g:method:getDhcpDscp"), [getDhcpFqdn]("GI.NM.Objects.SettingIP4Config#g:method:getDhcpFqdn"), [getDhcpHostname]("GI.NM.Objects.SettingIPConfig#g:method:getDhcpHostname"), [getDhcpHostnameFlags]("GI.NM.Objects.SettingIPConfig#g:method:getDhcpHostnameFlags"), [getDhcpIaid]("GI.NM.Objects.SettingIPConfig#g:method:getDhcpIaid"), [getDhcpRejectServers]("GI.NM.Objects.SettingIPConfig#g:method:getDhcpRejectServers"), [getDhcpSendHostname]("GI.NM.Objects.SettingIPConfig#g:method:getDhcpSendHostname"), [getDhcpSendRelease]("GI.NM.Objects.SettingIPConfig#g:method:getDhcpSendRelease"), [getDhcpTimeout]("GI.NM.Objects.SettingIPConfig#g:method:getDhcpTimeout"), [getDhcpVendorClassIdentifier]("GI.NM.Objects.SettingIP4Config#g:method:getDhcpVendorClassIdentifier"), [getDns]("GI.NM.Objects.SettingIPConfig#g:method:getDns"), [getDnsOption]("GI.NM.Objects.SettingIPConfig#g:method:getDnsOption"), [getDnsPriority]("GI.NM.Objects.SettingIPConfig#g:method:getDnsPriority"), [getDnsSearch]("GI.NM.Objects.SettingIPConfig#g:method:getDnsSearch"), [getGateway]("GI.NM.Objects.SettingIPConfig#g:method:getGateway"), [getIgnoreAutoDns]("GI.NM.Objects.SettingIPConfig#g:method:getIgnoreAutoDns"), [getIgnoreAutoRoutes]("GI.NM.Objects.SettingIPConfig#g:method:getIgnoreAutoRoutes"), [getLinkLocal]("GI.NM.Objects.SettingIP4Config#g:method:getLinkLocal"), [getMayFail]("GI.NM.Objects.SettingIPConfig#g:method:getMayFail"), [getMethod]("GI.NM.Objects.SettingIPConfig#g:method:getMethod"), [getName]("GI.NM.Objects.Setting#g:method:getName"), [getNeverDefault]("GI.NM.Objects.SettingIPConfig#g:method:getNeverDefault"), [getNumAddresses]("GI.NM.Objects.SettingIPConfig#g:method:getNumAddresses"), [getNumDns]("GI.NM.Objects.SettingIPConfig#g:method:getNumDns"), [getNumDnsOptions]("GI.NM.Objects.SettingIPConfig#g:method:getNumDnsOptions"), [getNumDnsSearches]("GI.NM.Objects.SettingIPConfig#g:method:getNumDnsSearches"), [getNumRoutes]("GI.NM.Objects.SettingIPConfig#g:method:getNumRoutes"), [getNumRoutingRules]("GI.NM.Objects.SettingIPConfig#g:method:getNumRoutingRules"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getReplaceLocalRule]("GI.NM.Objects.SettingIPConfig#g:method:getReplaceLocalRule"), [getRequiredTimeout]("GI.NM.Objects.SettingIPConfig#g:method:getRequiredTimeout"), [getRoute]("GI.NM.Objects.SettingIPConfig#g:method:getRoute"), [getRouteMetric]("GI.NM.Objects.SettingIPConfig#g:method:getRouteMetric"), [getRouteTable]("GI.NM.Objects.SettingIPConfig#g:method:getRouteTable"), [getRoutingRule]("GI.NM.Objects.SettingIPConfig#g:method:getRoutingRule"), [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)
    ResolveSettingIP4ConfigMethod           ,
#endif

-- ** getDhcpClientId #method:getDhcpClientId#

#if defined(ENABLE_OVERLOADING)
    SettingIP4ConfigGetDhcpClientIdMethodInfo,
#endif
    settingIP4ConfigGetDhcpClientId         ,


-- ** getDhcpFqdn #method:getDhcpFqdn#

#if defined(ENABLE_OVERLOADING)
    SettingIP4ConfigGetDhcpFqdnMethodInfo   ,
#endif
    settingIP4ConfigGetDhcpFqdn             ,


-- ** getDhcpVendorClassIdentifier #method:getDhcpVendorClassIdentifier#

#if defined(ENABLE_OVERLOADING)
    SettingIP4ConfigGetDhcpVendorClassIdentifierMethodInfo,
#endif
    settingIP4ConfigGetDhcpVendorClassIdentifier,


-- ** getLinkLocal #method:getLinkLocal#

#if defined(ENABLE_OVERLOADING)
    SettingIP4ConfigGetLinkLocalMethodInfo  ,
#endif
    settingIP4ConfigGetLinkLocal            ,


-- ** new #method:new#

    settingIP4ConfigNew                     ,




 -- * Properties


-- ** dhcpClientId #attr:dhcpClientId#
-- | A string sent to the DHCP server to identify the local machine which the
-- DHCP server may use to customize the DHCP lease and options.
-- When the property is a hex string (\'aa:bb:cc\') it is interpreted as a
-- binary client ID, in which case the first byte is assumed to be the
-- \'type\' field as per RFC 2132 section 9.14 and the remaining bytes may be
-- an hardware address (e.g. \'01:xx:xx:xx:xx:xx:xx\' where 1 is the Ethernet
-- ARP type and the rest is a MAC address).
-- If the property is not a hex string it is considered as a
-- non-hardware-address client ID and the \'type\' field is set to 0.
-- 
-- The special values \"mac\" and \"perm-mac\" are supported, which use the
-- current or permanent MAC address of the device to generate a client identifier
-- with type ethernet (01). Currently, these options only work for ethernet
-- type of links.
-- 
-- The special value \"ipv6-duid\" uses the DUID from \"ipv6.dhcp-duid\" property as
-- an RFC4361-compliant client identifier. As IAID it uses \"ipv4.dhcp-iaid\"
-- and falls back to \"ipv6.dhcp-iaid\" if unset.
-- 
-- The special value \"duid\" generates a RFC4361-compliant client identifier based
-- on \"ipv4.dhcp-iaid\" and uses a DUID generated by hashing \/etc\/machine-id.
-- 
-- The special value \"stable\" is supported to generate a type 0 client identifier based
-- on the stable-id (see connection.stable-id) and a per-host key. If you set the
-- stable-id, you may want to include the \"${DEVICE}\" or \"${MAC}\" specifier to get a
-- per-device key.
-- 
-- The special value \"none\" prevents any client identifier from being sent. Note that
-- this is normally not recommended.
-- 
-- If unset, a globally configured default from NetworkManager.conf is
-- used. If still unset, the default depends on the DHCP plugin. The
-- internal dhcp client will default to \"mac\" and the dhclient plugin will
-- try to use one from its config file if present, or won\'t sent any
-- client-id otherwise.

#if defined(ENABLE_OVERLOADING)
    SettingIP4ConfigDhcpClientIdPropertyInfo,
#endif
    clearSettingIP4ConfigDhcpClientId       ,
    constructSettingIP4ConfigDhcpClientId   ,
    getSettingIP4ConfigDhcpClientId         ,
    setSettingIP4ConfigDhcpClientId         ,
#if defined(ENABLE_OVERLOADING)
    settingIP4ConfigDhcpClientId            ,
#endif


-- ** dhcpFqdn #attr:dhcpFqdn#
-- | If the [SettingIPConfig:dhcpSendHostname]("GI.NM.Objects.SettingIPConfig#g:attr:dhcpSendHostname") property is 'P.True', then the
-- specified FQDN will be sent to the DHCP server when acquiring a lease. This
-- property and [SettingIPConfig:dhcpHostname]("GI.NM.Objects.SettingIPConfig#g:attr:dhcpHostname") are mutually exclusive and
-- cannot be set at the same time.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIP4ConfigDhcpFqdnPropertyInfo    ,
#endif
    clearSettingIP4ConfigDhcpFqdn           ,
    constructSettingIP4ConfigDhcpFqdn       ,
    getSettingIP4ConfigDhcpFqdn             ,
    setSettingIP4ConfigDhcpFqdn             ,
#if defined(ENABLE_OVERLOADING)
    settingIP4ConfigDhcpFqdn                ,
#endif


-- ** dhcpVendorClassIdentifier #attr:dhcpVendorClassIdentifier#
-- | The Vendor Class Identifier DHCP option (60).
-- Special characters in the data string may be escaped using C-style escapes,
-- nevertheless this property cannot contain nul bytes.
-- If the per-profile value is unspecified (the default),
-- a global connection default gets consulted.
-- If still unspecified, the DHCP option is not sent to the server.
-- 
-- /Since: 1.28/

#if defined(ENABLE_OVERLOADING)
    SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo,
#endif
    clearSettingIP4ConfigDhcpVendorClassIdentifier,
    constructSettingIP4ConfigDhcpVendorClassIdentifier,
    getSettingIP4ConfigDhcpVendorClassIdentifier,
    setSettingIP4ConfigDhcpVendorClassIdentifier,
#if defined(ENABLE_OVERLOADING)
    settingIP4ConfigDhcpVendorClassIdentifier,
#endif


-- ** linkLocal #attr:linkLocal#
-- | Enable and disable the IPv4 link-local configuration independently of the
-- ipv4.method configuration. This allows a link-local address (169.254.x.y\/16)
-- to be obtained in addition to other addresses, such as those manually
-- configured or obtained from a DHCP server.
-- 
-- When set to \"auto\", the value is dependent on \"ipv4.method\".
-- When set to \"default\", it honors the global connection default, before
-- falling back to \"auto\". Note that if \"ipv4.method\" is \"disabled\", then
-- link local addressing is always disabled too. The default is \"default\".
-- 
-- /Since: 1.40/

#if defined(ENABLE_OVERLOADING)
    SettingIP4ConfigLinkLocalPropertyInfo   ,
#endif
    constructSettingIP4ConfigLinkLocal      ,
    getSettingIP4ConfigLinkLocal            ,
    setSettingIP4ConfigLinkLocal            ,
#if defined(ENABLE_OVERLOADING)
    settingIP4ConfigLinkLocal               ,
#endif




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.NM.Callbacks as NM.Callbacks
import {-# SOURCE #-} qualified GI.NM.Enums as NM.Enums
import {-# SOURCE #-} qualified GI.NM.Flags as NM.Flags
import {-# SOURCE #-} qualified GI.NM.Interfaces.Connection as NM.Connection
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
import {-# SOURCE #-} qualified GI.NM.Objects.Setting8021x as NM.Setting8021x
import {-# SOURCE #-} qualified GI.NM.Objects.SettingAdsl as NM.SettingAdsl
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBluetooth as NM.SettingBluetooth
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBond as NM.SettingBond
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridge as NM.SettingBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridgePort as NM.SettingBridgePort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingCdma as NM.SettingCdma
import {-# SOURCE #-} qualified GI.NM.Objects.SettingConnection as NM.SettingConnection
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDcb as NM.SettingDcb
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDummy as NM.SettingDummy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGeneric as NM.SettingGeneric
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGsm as NM.SettingGsm
import {-# SOURCE #-} qualified GI.NM.Objects.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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.NM.Enums as NM.Enums
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPConfig as NM.SettingIPConfig

#endif

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

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

foreign import ccall "nm_setting_ip4_config_get_type"
    c_nm_setting_ip4_config_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingIP4Config where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_ip4_config_get_type

instance B.Types.GObject SettingIP4Config

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSettingIP4ConfigMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSettingIP4ConfigMethod "addAddress" o = NM.SettingIPConfig.SettingIPConfigAddAddressMethodInfo
    ResolveSettingIP4ConfigMethod "addDhcpRejectServer" o = NM.SettingIPConfig.SettingIPConfigAddDhcpRejectServerMethodInfo
    ResolveSettingIP4ConfigMethod "addDns" o = NM.SettingIPConfig.SettingIPConfigAddDnsMethodInfo
    ResolveSettingIP4ConfigMethod "addDnsOption" o = NM.SettingIPConfig.SettingIPConfigAddDnsOptionMethodInfo
    ResolveSettingIP4ConfigMethod "addDnsSearch" o = NM.SettingIPConfig.SettingIPConfigAddDnsSearchMethodInfo
    ResolveSettingIP4ConfigMethod "addRoute" o = NM.SettingIPConfig.SettingIPConfigAddRouteMethodInfo
    ResolveSettingIP4ConfigMethod "addRoutingRule" o = NM.SettingIPConfig.SettingIPConfigAddRoutingRuleMethodInfo
    ResolveSettingIP4ConfigMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSettingIP4ConfigMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSettingIP4ConfigMethod "clearAddresses" o = NM.SettingIPConfig.SettingIPConfigClearAddressesMethodInfo
    ResolveSettingIP4ConfigMethod "clearDhcpRejectServers" o = NM.SettingIPConfig.SettingIPConfigClearDhcpRejectServersMethodInfo
    ResolveSettingIP4ConfigMethod "clearDns" o = NM.SettingIPConfig.SettingIPConfigClearDnsMethodInfo
    ResolveSettingIP4ConfigMethod "clearDnsOptions" o = NM.SettingIPConfig.SettingIPConfigClearDnsOptionsMethodInfo
    ResolveSettingIP4ConfigMethod "clearDnsSearches" o = NM.SettingIPConfig.SettingIPConfigClearDnsSearchesMethodInfo
    ResolveSettingIP4ConfigMethod "clearRoutes" o = NM.SettingIPConfig.SettingIPConfigClearRoutesMethodInfo
    ResolveSettingIP4ConfigMethod "clearRoutingRules" o = NM.SettingIPConfig.SettingIPConfigClearRoutingRulesMethodInfo
    ResolveSettingIP4ConfigMethod "compare" o = NM.Setting.SettingCompareMethodInfo
    ResolveSettingIP4ConfigMethod "diff" o = NM.Setting.SettingDiffMethodInfo
    ResolveSettingIP4ConfigMethod "duplicate" o = NM.Setting.SettingDuplicateMethodInfo
    ResolveSettingIP4ConfigMethod "enumerateValues" o = NM.Setting.SettingEnumerateValuesMethodInfo
    ResolveSettingIP4ConfigMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSettingIP4ConfigMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSettingIP4ConfigMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSettingIP4ConfigMethod "hasDnsOptions" o = NM.SettingIPConfig.SettingIPConfigHasDnsOptionsMethodInfo
    ResolveSettingIP4ConfigMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSettingIP4ConfigMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSettingIP4ConfigMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSettingIP4ConfigMethod "optionClearByName" o = NM.Setting.SettingOptionClearByNameMethodInfo
    ResolveSettingIP4ConfigMethod "optionGet" o = NM.Setting.SettingOptionGetMethodInfo
    ResolveSettingIP4ConfigMethod "optionGetAllNames" o = NM.Setting.SettingOptionGetAllNamesMethodInfo
    ResolveSettingIP4ConfigMethod "optionGetBoolean" o = NM.Setting.SettingOptionGetBooleanMethodInfo
    ResolveSettingIP4ConfigMethod "optionGetUint32" o = NM.Setting.SettingOptionGetUint32MethodInfo
    ResolveSettingIP4ConfigMethod "optionSet" o = NM.Setting.SettingOptionSetMethodInfo
    ResolveSettingIP4ConfigMethod "optionSetBoolean" o = NM.Setting.SettingOptionSetBooleanMethodInfo
    ResolveSettingIP4ConfigMethod "optionSetUint32" o = NM.Setting.SettingOptionSetUint32MethodInfo
    ResolveSettingIP4ConfigMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSettingIP4ConfigMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSettingIP4ConfigMethod "removeAddress" o = NM.SettingIPConfig.SettingIPConfigRemoveAddressMethodInfo
    ResolveSettingIP4ConfigMethod "removeAddressByValue" o = NM.SettingIPConfig.SettingIPConfigRemoveAddressByValueMethodInfo
    ResolveSettingIP4ConfigMethod "removeDhcpRejectServer" o = NM.SettingIPConfig.SettingIPConfigRemoveDhcpRejectServerMethodInfo
    ResolveSettingIP4ConfigMethod "removeDns" o = NM.SettingIPConfig.SettingIPConfigRemoveDnsMethodInfo
    ResolveSettingIP4ConfigMethod "removeDnsByValue" o = NM.SettingIPConfig.SettingIPConfigRemoveDnsByValueMethodInfo
    ResolveSettingIP4ConfigMethod "removeDnsOption" o = NM.SettingIPConfig.SettingIPConfigRemoveDnsOptionMethodInfo
    ResolveSettingIP4ConfigMethod "removeDnsOptionByValue" o = NM.SettingIPConfig.SettingIPConfigRemoveDnsOptionByValueMethodInfo
    ResolveSettingIP4ConfigMethod "removeDnsSearch" o = NM.SettingIPConfig.SettingIPConfigRemoveDnsSearchMethodInfo
    ResolveSettingIP4ConfigMethod "removeDnsSearchByValue" o = NM.SettingIPConfig.SettingIPConfigRemoveDnsSearchByValueMethodInfo
    ResolveSettingIP4ConfigMethod "removeRoute" o = NM.SettingIPConfig.SettingIPConfigRemoveRouteMethodInfo
    ResolveSettingIP4ConfigMethod "removeRouteByValue" o = NM.SettingIPConfig.SettingIPConfigRemoveRouteByValueMethodInfo
    ResolveSettingIP4ConfigMethod "removeRoutingRule" o = NM.SettingIPConfig.SettingIPConfigRemoveRoutingRuleMethodInfo
    ResolveSettingIP4ConfigMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSettingIP4ConfigMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSettingIP4ConfigMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSettingIP4ConfigMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSettingIP4ConfigMethod "toString" o = NM.Setting.SettingToStringMethodInfo
    ResolveSettingIP4ConfigMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSettingIP4ConfigMethod "verify" o = NM.Setting.SettingVerifyMethodInfo
    ResolveSettingIP4ConfigMethod "verifySecrets" o = NM.Setting.SettingVerifySecretsMethodInfo
    ResolveSettingIP4ConfigMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSettingIP4ConfigMethod "getAddress" o = NM.SettingIPConfig.SettingIPConfigGetAddressMethodInfo
    ResolveSettingIP4ConfigMethod "getAutoRouteExtGw" o = NM.SettingIPConfig.SettingIPConfigGetAutoRouteExtGwMethodInfo
    ResolveSettingIP4ConfigMethod "getDadTimeout" o = NM.SettingIPConfig.SettingIPConfigGetDadTimeoutMethodInfo
    ResolveSettingIP4ConfigMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSettingIP4ConfigMethod "getDbusPropertyType" o = NM.Setting.SettingGetDbusPropertyTypeMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpClientId" o = SettingIP4ConfigGetDhcpClientIdMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpDscp" o = NM.SettingIPConfig.SettingIPConfigGetDhcpDscpMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpFqdn" o = SettingIP4ConfigGetDhcpFqdnMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpHostname" o = NM.SettingIPConfig.SettingIPConfigGetDhcpHostnameMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpHostnameFlags" o = NM.SettingIPConfig.SettingIPConfigGetDhcpHostnameFlagsMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpIaid" o = NM.SettingIPConfig.SettingIPConfigGetDhcpIaidMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpRejectServers" o = NM.SettingIPConfig.SettingIPConfigGetDhcpRejectServersMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpSendHostname" o = NM.SettingIPConfig.SettingIPConfigGetDhcpSendHostnameMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpSendRelease" o = NM.SettingIPConfig.SettingIPConfigGetDhcpSendReleaseMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpTimeout" o = NM.SettingIPConfig.SettingIPConfigGetDhcpTimeoutMethodInfo
    ResolveSettingIP4ConfigMethod "getDhcpVendorClassIdentifier" o = SettingIP4ConfigGetDhcpVendorClassIdentifierMethodInfo
    ResolveSettingIP4ConfigMethod "getDns" o = NM.SettingIPConfig.SettingIPConfigGetDnsMethodInfo
    ResolveSettingIP4ConfigMethod "getDnsOption" o = NM.SettingIPConfig.SettingIPConfigGetDnsOptionMethodInfo
    ResolveSettingIP4ConfigMethod "getDnsPriority" o = NM.SettingIPConfig.SettingIPConfigGetDnsPriorityMethodInfo
    ResolveSettingIP4ConfigMethod "getDnsSearch" o = NM.SettingIPConfig.SettingIPConfigGetDnsSearchMethodInfo
    ResolveSettingIP4ConfigMethod "getGateway" o = NM.SettingIPConfig.SettingIPConfigGetGatewayMethodInfo
    ResolveSettingIP4ConfigMethod "getIgnoreAutoDns" o = NM.SettingIPConfig.SettingIPConfigGetIgnoreAutoDnsMethodInfo
    ResolveSettingIP4ConfigMethod "getIgnoreAutoRoutes" o = NM.SettingIPConfig.SettingIPConfigGetIgnoreAutoRoutesMethodInfo
    ResolveSettingIP4ConfigMethod "getLinkLocal" o = SettingIP4ConfigGetLinkLocalMethodInfo
    ResolveSettingIP4ConfigMethod "getMayFail" o = NM.SettingIPConfig.SettingIPConfigGetMayFailMethodInfo
    ResolveSettingIP4ConfigMethod "getMethod" o = NM.SettingIPConfig.SettingIPConfigGetMethodMethodInfo
    ResolveSettingIP4ConfigMethod "getName" o = NM.Setting.SettingGetNameMethodInfo
    ResolveSettingIP4ConfigMethod "getNeverDefault" o = NM.SettingIPConfig.SettingIPConfigGetNeverDefaultMethodInfo
    ResolveSettingIP4ConfigMethod "getNumAddresses" o = NM.SettingIPConfig.SettingIPConfigGetNumAddressesMethodInfo
    ResolveSettingIP4ConfigMethod "getNumDns" o = NM.SettingIPConfig.SettingIPConfigGetNumDnsMethodInfo
    ResolveSettingIP4ConfigMethod "getNumDnsOptions" o = NM.SettingIPConfig.SettingIPConfigGetNumDnsOptionsMethodInfo
    ResolveSettingIP4ConfigMethod "getNumDnsSearches" o = NM.SettingIPConfig.SettingIPConfigGetNumDnsSearchesMethodInfo
    ResolveSettingIP4ConfigMethod "getNumRoutes" o = NM.SettingIPConfig.SettingIPConfigGetNumRoutesMethodInfo
    ResolveSettingIP4ConfigMethod "getNumRoutingRules" o = NM.SettingIPConfig.SettingIPConfigGetNumRoutingRulesMethodInfo
    ResolveSettingIP4ConfigMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingIP4ConfigMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingIP4ConfigMethod "getReplaceLocalRule" o = NM.SettingIPConfig.SettingIPConfigGetReplaceLocalRuleMethodInfo
    ResolveSettingIP4ConfigMethod "getRequiredTimeout" o = NM.SettingIPConfig.SettingIPConfigGetRequiredTimeoutMethodInfo
    ResolveSettingIP4ConfigMethod "getRoute" o = NM.SettingIPConfig.SettingIPConfigGetRouteMethodInfo
    ResolveSettingIP4ConfigMethod "getRouteMetric" o = NM.SettingIPConfig.SettingIPConfigGetRouteMetricMethodInfo
    ResolveSettingIP4ConfigMethod "getRouteTable" o = NM.SettingIPConfig.SettingIPConfigGetRouteTableMethodInfo
    ResolveSettingIP4ConfigMethod "getRoutingRule" o = NM.SettingIPConfig.SettingIPConfigGetRoutingRuleMethodInfo
    ResolveSettingIP4ConfigMethod "getSecretFlags" o = NM.Setting.SettingGetSecretFlagsMethodInfo
    ResolveSettingIP4ConfigMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingIP4ConfigMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingIP4ConfigMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingIP4ConfigMethod "setSecretFlags" o = NM.Setting.SettingSetSecretFlagsMethodInfo
    ResolveSettingIP4ConfigMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data SettingIP4ConfigDhcpClientIdPropertyInfo
instance AttrInfo SettingIP4ConfigDhcpClientIdPropertyInfo where
    type AttrAllowedOps SettingIP4ConfigDhcpClientIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingIP4ConfigDhcpClientIdPropertyInfo = IsSettingIP4Config
    type AttrSetTypeConstraint SettingIP4ConfigDhcpClientIdPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingIP4ConfigDhcpClientIdPropertyInfo = (~) T.Text
    type AttrTransferType SettingIP4ConfigDhcpClientIdPropertyInfo = T.Text
    type AttrGetType SettingIP4ConfigDhcpClientIdPropertyInfo = T.Text
    type AttrLabel SettingIP4ConfigDhcpClientIdPropertyInfo = "dhcp-client-id"
    type AttrOrigin SettingIP4ConfigDhcpClientIdPropertyInfo = SettingIP4Config
    attrGet = getSettingIP4ConfigDhcpClientId
    attrSet = setSettingIP4ConfigDhcpClientId
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIP4ConfigDhcpClientId
    attrClear = clearSettingIP4ConfigDhcpClientId
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIP4Config.dhcpClientId"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIP4Config.html#g:attr:dhcpClientId"
        })
#endif

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data SettingIP4ConfigDhcpFqdnPropertyInfo
instance AttrInfo SettingIP4ConfigDhcpFqdnPropertyInfo where
    type AttrAllowedOps SettingIP4ConfigDhcpFqdnPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingIP4ConfigDhcpFqdnPropertyInfo = IsSettingIP4Config
    type AttrSetTypeConstraint SettingIP4ConfigDhcpFqdnPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingIP4ConfigDhcpFqdnPropertyInfo = (~) T.Text
    type AttrTransferType SettingIP4ConfigDhcpFqdnPropertyInfo = T.Text
    type AttrGetType SettingIP4ConfigDhcpFqdnPropertyInfo = T.Text
    type AttrLabel SettingIP4ConfigDhcpFqdnPropertyInfo = "dhcp-fqdn"
    type AttrOrigin SettingIP4ConfigDhcpFqdnPropertyInfo = SettingIP4Config
    attrGet = getSettingIP4ConfigDhcpFqdn
    attrSet = setSettingIP4ConfigDhcpFqdn
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIP4ConfigDhcpFqdn
    attrClear = clearSettingIP4ConfigDhcpFqdn
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIP4Config.dhcpFqdn"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIP4Config.html#g:attr:dhcpFqdn"
        })
#endif

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

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

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

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

-- | Set the value of the “@dhcp-vendor-class-identifier@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #dhcpVendorClassIdentifier
-- @
clearSettingIP4ConfigDhcpVendorClassIdentifier :: (MonadIO m, IsSettingIP4Config o) => o -> m ()
clearSettingIP4ConfigDhcpVendorClassIdentifier :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIP4Config o) =>
o -> m ()
clearSettingIP4ConfigDhcpVendorClassIdentifier o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"dhcp-vendor-class-identifier" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo
instance AttrInfo SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo where
    type AttrAllowedOps SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo = IsSettingIP4Config
    type AttrSetTypeConstraint SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo = (~) T.Text
    type AttrTransferType SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo = T.Text
    type AttrGetType SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo = T.Text
    type AttrLabel SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo = "dhcp-vendor-class-identifier"
    type AttrOrigin SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo = SettingIP4Config
    attrGet = getSettingIP4ConfigDhcpVendorClassIdentifier
    attrSet = setSettingIP4ConfigDhcpVendorClassIdentifier
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIP4ConfigDhcpVendorClassIdentifier
    attrClear = clearSettingIP4ConfigDhcpVendorClassIdentifier
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIP4Config.dhcpVendorClassIdentifier"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIP4Config.html#g:attr:dhcpVendorClassIdentifier"
        })
#endif

-- VVV Prop "link-local"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@link-local@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingIP4Config #linkLocal
-- @
getSettingIP4ConfigLinkLocal :: (MonadIO m, IsSettingIP4Config o) => o -> m Int32
getSettingIP4ConfigLinkLocal :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIP4Config o) =>
o -> m Int32
getSettingIP4ConfigLinkLocal o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"link-local"

-- | Set the value of the “@link-local@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingIP4Config [ #linkLocal 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIP4ConfigLinkLocal :: (MonadIO m, IsSettingIP4Config o) => o -> Int32 -> m ()
setSettingIP4ConfigLinkLocal :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIP4Config o) =>
o -> Int32 -> m ()
setSettingIP4ConfigLinkLocal o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"link-local" Int32
val

-- | Construct a t'GValueConstruct' with valid value for the “@link-local@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingIP4ConfigLinkLocal :: (IsSettingIP4Config o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingIP4ConfigLinkLocal :: forall o (m :: * -> *).
(IsSettingIP4Config o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingIP4ConfigLinkLocal Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"link-local" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingIP4ConfigLinkLocalPropertyInfo
instance AttrInfo SettingIP4ConfigLinkLocalPropertyInfo where
    type AttrAllowedOps SettingIP4ConfigLinkLocalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingIP4ConfigLinkLocalPropertyInfo = IsSettingIP4Config
    type AttrSetTypeConstraint SettingIP4ConfigLinkLocalPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingIP4ConfigLinkLocalPropertyInfo = (~) Int32
    type AttrTransferType SettingIP4ConfigLinkLocalPropertyInfo = Int32
    type AttrGetType SettingIP4ConfigLinkLocalPropertyInfo = Int32
    type AttrLabel SettingIP4ConfigLinkLocalPropertyInfo = "link-local"
    type AttrOrigin SettingIP4ConfigLinkLocalPropertyInfo = SettingIP4Config
    attrGet = getSettingIP4ConfigLinkLocal
    attrSet = setSettingIP4ConfigLinkLocal
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIP4ConfigLinkLocal
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIP4Config.linkLocal"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIP4Config.html#g:attr:linkLocal"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingIP4Config
type instance O.AttributeList SettingIP4Config = SettingIP4ConfigAttributeList
type SettingIP4ConfigAttributeList = ('[ '("addresses", NM.SettingIPConfig.SettingIPConfigAddressesPropertyInfo), '("autoRouteExtGw", NM.SettingIPConfig.SettingIPConfigAutoRouteExtGwPropertyInfo), '("dadTimeout", NM.SettingIPConfig.SettingIPConfigDadTimeoutPropertyInfo), '("dhcpClientId", SettingIP4ConfigDhcpClientIdPropertyInfo), '("dhcpDscp", NM.SettingIPConfig.SettingIPConfigDhcpDscpPropertyInfo), '("dhcpFqdn", SettingIP4ConfigDhcpFqdnPropertyInfo), '("dhcpHostname", NM.SettingIPConfig.SettingIPConfigDhcpHostnamePropertyInfo), '("dhcpHostnameFlags", NM.SettingIPConfig.SettingIPConfigDhcpHostnameFlagsPropertyInfo), '("dhcpIaid", NM.SettingIPConfig.SettingIPConfigDhcpIaidPropertyInfo), '("dhcpRejectServers", NM.SettingIPConfig.SettingIPConfigDhcpRejectServersPropertyInfo), '("dhcpSendHostname", NM.SettingIPConfig.SettingIPConfigDhcpSendHostnamePropertyInfo), '("dhcpSendRelease", NM.SettingIPConfig.SettingIPConfigDhcpSendReleasePropertyInfo), '("dhcpTimeout", NM.SettingIPConfig.SettingIPConfigDhcpTimeoutPropertyInfo), '("dhcpVendorClassIdentifier", SettingIP4ConfigDhcpVendorClassIdentifierPropertyInfo), '("dns", NM.SettingIPConfig.SettingIPConfigDnsPropertyInfo), '("dnsOptions", NM.SettingIPConfig.SettingIPConfigDnsOptionsPropertyInfo), '("dnsPriority", NM.SettingIPConfig.SettingIPConfigDnsPriorityPropertyInfo), '("dnsSearch", NM.SettingIPConfig.SettingIPConfigDnsSearchPropertyInfo), '("gateway", NM.SettingIPConfig.SettingIPConfigGatewayPropertyInfo), '("ignoreAutoDns", NM.SettingIPConfig.SettingIPConfigIgnoreAutoDnsPropertyInfo), '("ignoreAutoRoutes", NM.SettingIPConfig.SettingIPConfigIgnoreAutoRoutesPropertyInfo), '("linkLocal", SettingIP4ConfigLinkLocalPropertyInfo), '("mayFail", NM.SettingIPConfig.SettingIPConfigMayFailPropertyInfo), '("method", NM.SettingIPConfig.SettingIPConfigMethodPropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("neverDefault", NM.SettingIPConfig.SettingIPConfigNeverDefaultPropertyInfo), '("replaceLocalRule", NM.SettingIPConfig.SettingIPConfigReplaceLocalRulePropertyInfo), '("requiredTimeout", NM.SettingIPConfig.SettingIPConfigRequiredTimeoutPropertyInfo), '("routeMetric", NM.SettingIPConfig.SettingIPConfigRouteMetricPropertyInfo), '("routeTable", NM.SettingIPConfig.SettingIPConfigRouteTablePropertyInfo), '("routes", NM.SettingIPConfig.SettingIPConfigRoutesPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingIP4ConfigDhcpClientId :: AttrLabelProxy "dhcpClientId"
settingIP4ConfigDhcpClientId = AttrLabelProxy

settingIP4ConfigDhcpFqdn :: AttrLabelProxy "dhcpFqdn"
settingIP4ConfigDhcpFqdn = AttrLabelProxy

settingIP4ConfigDhcpVendorClassIdentifier :: AttrLabelProxy "dhcpVendorClassIdentifier"
settingIP4ConfigDhcpVendorClassIdentifier = AttrLabelProxy

settingIP4ConfigLinkLocal :: AttrLabelProxy "linkLocal"
settingIP4ConfigLinkLocal = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "nm_setting_ip4_config_new" nm_setting_ip4_config_new :: 
    IO (Ptr SettingIP4Config)

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

#if defined(ENABLE_OVERLOADING)
#endif

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

-- | Returns the value contained in the [SettingIP4Config:dhcpClientId]("GI.NM.Objects.SettingIP4Config#g:attr:dhcpClientId")
-- property.
settingIP4ConfigGetDhcpClientId ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIP4Config a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIP4Config.SettingIP4Config'
    -> m T.Text
    -- ^ __Returns:__ the configured Client ID to send to the DHCP server when requesting
    -- addresses via DHCP.
settingIP4ConfigGetDhcpClientId :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIP4Config a) =>
a -> m Text
settingIP4ConfigGetDhcpClientId 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 SettingIP4Config
setting' <- a -> IO (Ptr SettingIP4Config)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingIP4Config -> IO CString
nm_setting_ip4_config_get_dhcp_client_id Ptr SettingIP4Config
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingIP4ConfigGetDhcpClientId" 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 SettingIP4ConfigGetDhcpClientIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingIP4Config a) => O.OverloadedMethod SettingIP4ConfigGetDhcpClientIdMethodInfo a signature where
    overloadedMethod = settingIP4ConfigGetDhcpClientId

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


#endif

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

-- | Returns the value contained in the [SettingIP4Config:dhcpFqdn]("GI.NM.Objects.SettingIP4Config#g:attr:dhcpFqdn")
-- property.
-- 
-- /Since: 1.2/
settingIP4ConfigGetDhcpFqdn ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIP4Config a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIP4Config.SettingIP4Config'
    -> m T.Text
    -- ^ __Returns:__ the configured FQDN to send to the DHCP server
settingIP4ConfigGetDhcpFqdn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIP4Config a) =>
a -> m Text
settingIP4ConfigGetDhcpFqdn 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 SettingIP4Config
setting' <- a -> IO (Ptr SettingIP4Config)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingIP4Config -> IO CString
nm_setting_ip4_config_get_dhcp_fqdn Ptr SettingIP4Config
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingIP4ConfigGetDhcpFqdn" 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 SettingIP4ConfigGetDhcpFqdnMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingIP4Config a) => O.OverloadedMethod SettingIP4ConfigGetDhcpFqdnMethodInfo a signature where
    overloadedMethod = settingIP4ConfigGetDhcpFqdn

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


#endif

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

-- | Returns the value contained in the t'GI.NM.Objects.SettingIP4Config.SettingIP4Config':@/dhcp_vendor_class_identifier/@
-- property.
-- 
-- /Since: 1.28/
settingIP4ConfigGetDhcpVendorClassIdentifier ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIP4Config a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIP4Config.SettingIP4Config'
    -> m T.Text
    -- ^ __Returns:__ the vendor class identifier option to send to the DHCP server
settingIP4ConfigGetDhcpVendorClassIdentifier :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIP4Config a) =>
a -> m Text
settingIP4ConfigGetDhcpVendorClassIdentifier 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 SettingIP4Config
setting' <- a -> IO (Ptr SettingIP4Config)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingIP4Config -> IO CString
nm_setting_ip4_config_get_dhcp_vendor_class_identifier Ptr SettingIP4Config
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingIP4ConfigGetDhcpVendorClassIdentifier" 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 SettingIP4ConfigGetDhcpVendorClassIdentifierMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingIP4Config a) => O.OverloadedMethod SettingIP4ConfigGetDhcpVendorClassIdentifierMethodInfo a signature where
    overloadedMethod = settingIP4ConfigGetDhcpVendorClassIdentifier

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


#endif

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

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

-- | Returns the value contained in the t'GI.NM.Objects.SettingIP4Config.SettingIP4Config':@/link_local/@
-- property.
-- 
-- /Since: 1.42/
settingIP4ConfigGetLinkLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIP4Config a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIP4Config.SettingIP4Config'
    -> m NM.Enums.SettingIP4LinkLocal
    -- ^ __Returns:__ the link-local configuration
settingIP4ConfigGetLinkLocal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIP4Config a) =>
a -> m SettingIP4LinkLocal
settingIP4ConfigGetLinkLocal a
setting = IO SettingIP4LinkLocal -> m SettingIP4LinkLocal
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingIP4LinkLocal -> m SettingIP4LinkLocal)
-> IO SettingIP4LinkLocal -> m SettingIP4LinkLocal
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingIP4Config
setting' <- a -> IO (Ptr SettingIP4Config)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CUInt
result <- Ptr SettingIP4Config -> IO CUInt
nm_setting_ip4_config_get_link_local Ptr SettingIP4Config
setting'
    let result' :: SettingIP4LinkLocal
result' = (Int -> SettingIP4LinkLocal
forall a. Enum a => Int -> a
toEnum (Int -> SettingIP4LinkLocal)
-> (CUInt -> Int) -> CUInt -> SettingIP4LinkLocal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    SettingIP4LinkLocal -> IO SettingIP4LinkLocal
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SettingIP4LinkLocal
result'

#if defined(ENABLE_OVERLOADING)
data SettingIP4ConfigGetLinkLocalMethodInfo
instance (signature ~ (m NM.Enums.SettingIP4LinkLocal), MonadIO m, IsSettingIP4Config a) => O.OverloadedMethod SettingIP4ConfigGetLinkLocalMethodInfo a signature where
    overloadedMethod = settingIP4ConfigGetLinkLocal

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


#endif