{-# LANGUAGE TypeApplications #-}


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

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

module GI.NM.Objects.SettingVxlan
    ( 

-- * Exported types
    SettingVxlan(..)                        ,
    IsSettingVxlan                          ,
    toSettingVxlan                          ,


 -- * 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
-- [getAgeing]("GI.NM.Objects.SettingVxlan#g:method:getAgeing"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDbusPropertyType]("GI.NM.Objects.Setting#g:method:getDbusPropertyType"), [getDestinationPort]("GI.NM.Objects.SettingVxlan#g:method:getDestinationPort"), [getId]("GI.NM.Objects.SettingVxlan#g:method:getId"), [getL2Miss]("GI.NM.Objects.SettingVxlan#g:method:getL2Miss"), [getL3Miss]("GI.NM.Objects.SettingVxlan#g:method:getL3Miss"), [getLearning]("GI.NM.Objects.SettingVxlan#g:method:getLearning"), [getLimit]("GI.NM.Objects.SettingVxlan#g:method:getLimit"), [getLocal]("GI.NM.Objects.SettingVxlan#g:method:getLocal"), [getName]("GI.NM.Objects.Setting#g:method:getName"), [getParent]("GI.NM.Objects.SettingVxlan#g:method:getParent"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getProxy]("GI.NM.Objects.SettingVxlan#g:method:getProxy"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRemote]("GI.NM.Objects.SettingVxlan#g:method:getRemote"), [getRsc]("GI.NM.Objects.SettingVxlan#g:method:getRsc"), [getSecretFlags]("GI.NM.Objects.Setting#g:method:getSecretFlags"), [getSourcePortMax]("GI.NM.Objects.SettingVxlan#g:method:getSourcePortMax"), [getSourcePortMin]("GI.NM.Objects.SettingVxlan#g:method:getSourcePortMin"), [getTos]("GI.NM.Objects.SettingVxlan#g:method:getTos"), [getTtl]("GI.NM.Objects.SettingVxlan#g:method:getTtl").
-- 
-- ==== 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)
    ResolveSettingVxlanMethod               ,
#endif

-- ** getAgeing #method:getAgeing#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetAgeingMethodInfo         ,
#endif
    settingVxlanGetAgeing                   ,


-- ** getDestinationPort #method:getDestinationPort#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetDestinationPortMethodInfo,
#endif
    settingVxlanGetDestinationPort          ,


-- ** getId #method:getId#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetIdMethodInfo             ,
#endif
    settingVxlanGetId                       ,


-- ** getL2Miss #method:getL2Miss#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetL2MissMethodInfo         ,
#endif
    settingVxlanGetL2Miss                   ,


-- ** getL3Miss #method:getL3Miss#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetL3MissMethodInfo         ,
#endif
    settingVxlanGetL3Miss                   ,


-- ** getLearning #method:getLearning#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetLearningMethodInfo       ,
#endif
    settingVxlanGetLearning                 ,


-- ** getLimit #method:getLimit#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetLimitMethodInfo          ,
#endif
    settingVxlanGetLimit                    ,


-- ** getLocal #method:getLocal#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetLocalMethodInfo          ,
#endif
    settingVxlanGetLocal                    ,


-- ** getParent #method:getParent#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetParentMethodInfo         ,
#endif
    settingVxlanGetParent                   ,


-- ** getProxy #method:getProxy#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetProxyMethodInfo          ,
#endif
    settingVxlanGetProxy                    ,


-- ** getRemote #method:getRemote#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetRemoteMethodInfo         ,
#endif
    settingVxlanGetRemote                   ,


-- ** getRsc #method:getRsc#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetRscMethodInfo            ,
#endif
    settingVxlanGetRsc                      ,


-- ** getSourcePortMax #method:getSourcePortMax#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetSourcePortMaxMethodInfo  ,
#endif
    settingVxlanGetSourcePortMax            ,


-- ** getSourcePortMin #method:getSourcePortMin#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetSourcePortMinMethodInfo  ,
#endif
    settingVxlanGetSourcePortMin            ,


-- ** getTos #method:getTos#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetTosMethodInfo            ,
#endif
    settingVxlanGetTos                      ,


-- ** getTtl #method:getTtl#

#if defined(ENABLE_OVERLOADING)
    SettingVxlanGetTtlMethodInfo            ,
#endif
    settingVxlanGetTtl                      ,


-- ** new #method:new#

    settingVxlanNew                         ,




 -- * Properties


-- ** ageing #attr:ageing#
-- | Specifies the lifetime in seconds of FDB entries learnt by the kernel.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanAgeingPropertyInfo          ,
#endif
    constructSettingVxlanAgeing             ,
    getSettingVxlanAgeing                   ,
    setSettingVxlanAgeing                   ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanAgeing                      ,
#endif


-- ** destinationPort #attr:destinationPort#
-- | Specifies the UDP destination port to communicate to the remote VXLAN
-- tunnel endpoint.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanDestinationPortPropertyInfo ,
#endif
    constructSettingVxlanDestinationPort    ,
    getSettingVxlanDestinationPort          ,
    setSettingVxlanDestinationPort          ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanDestinationPort             ,
#endif


-- ** id #attr:id#
-- | Specifies the VXLAN Network Identifier (or VXLAN Segment Identifier) to
-- use.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanIdPropertyInfo              ,
#endif
    constructSettingVxlanId                 ,
    getSettingVxlanId                       ,
    setSettingVxlanId                       ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanId                          ,
#endif


-- ** l2Miss #attr:l2Miss#
-- | Specifies whether netlink LL ADDR miss notifications are generated.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanL2MissPropertyInfo          ,
#endif
    constructSettingVxlanL2Miss             ,
    getSettingVxlanL2Miss                   ,
    setSettingVxlanL2Miss                   ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanL2Miss                      ,
#endif


-- ** l3Miss #attr:l3Miss#
-- | Specifies whether netlink IP ADDR miss notifications are generated.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanL3MissPropertyInfo          ,
#endif
    constructSettingVxlanL3Miss             ,
    getSettingVxlanL3Miss                   ,
    setSettingVxlanL3Miss                   ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanL3Miss                      ,
#endif


-- ** learning #attr:learning#
-- | Specifies whether unknown source link layer addresses and IP addresses
-- are entered into the VXLAN device forwarding database.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanLearningPropertyInfo        ,
#endif
    constructSettingVxlanLearning           ,
    getSettingVxlanLearning                 ,
    setSettingVxlanLearning                 ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanLearning                    ,
#endif


-- ** limit #attr:limit#
-- | Specifies the maximum number of FDB entries. A value of zero means that
-- the kernel will store unlimited entries.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanLimitPropertyInfo           ,
#endif
    constructSettingVxlanLimit              ,
    getSettingVxlanLimit                    ,
    setSettingVxlanLimit                    ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanLimit                       ,
#endif


-- ** local #attr:local#
-- | If given, specifies the source IP address to use in outgoing packets.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanLocalPropertyInfo           ,
#endif
    clearSettingVxlanLocal                  ,
    constructSettingVxlanLocal              ,
    getSettingVxlanLocal                    ,
    setSettingVxlanLocal                    ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanLocal                       ,
#endif


-- ** parent #attr:parent#
-- | If given, specifies the parent interface name or parent connection UUID.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanParentPropertyInfo          ,
#endif
    clearSettingVxlanParent                 ,
    constructSettingVxlanParent             ,
    getSettingVxlanParent                   ,
    setSettingVxlanParent                   ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanParent                      ,
#endif


-- ** proxy #attr:proxy#
-- | Specifies whether ARP proxy is turned on.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanProxyPropertyInfo           ,
#endif
    constructSettingVxlanProxy              ,
    getSettingVxlanProxy                    ,
    setSettingVxlanProxy                    ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanProxy                       ,
#endif


-- ** remote #attr:remote#
-- | Specifies the unicast destination IP address to use in outgoing packets
-- when the destination link layer address is not known in the VXLAN device
-- forwarding database, or the multicast IP address to join.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanRemotePropertyInfo          ,
#endif
    clearSettingVxlanRemote                 ,
    constructSettingVxlanRemote             ,
    getSettingVxlanRemote                   ,
    setSettingVxlanRemote                   ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanRemote                      ,
#endif


-- ** rsc #attr:rsc#
-- | Specifies whether route short circuit is turned on.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanRscPropertyInfo             ,
#endif
    constructSettingVxlanRsc                ,
    getSettingVxlanRsc                      ,
    setSettingVxlanRsc                      ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanRsc                         ,
#endif


-- ** sourcePortMax #attr:sourcePortMax#
-- | Specifies the maximum UDP source port to communicate to the remote VXLAN
-- tunnel endpoint.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanSourcePortMaxPropertyInfo   ,
#endif
    constructSettingVxlanSourcePortMax      ,
    getSettingVxlanSourcePortMax            ,
    setSettingVxlanSourcePortMax            ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanSourcePortMax               ,
#endif


-- ** sourcePortMin #attr:sourcePortMin#
-- | Specifies the minimum UDP source port to communicate to the remote VXLAN
-- tunnel endpoint.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanSourcePortMinPropertyInfo   ,
#endif
    constructSettingVxlanSourcePortMin      ,
    getSettingVxlanSourcePortMin            ,
    setSettingVxlanSourcePortMin            ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanSourcePortMin               ,
#endif


-- ** tos #attr:tos#
-- | Specifies the TOS value to use in outgoing packets.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanTosPropertyInfo             ,
#endif
    constructSettingVxlanTos                ,
    getSettingVxlanTos                      ,
    setSettingVxlanTos                      ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanTos                         ,
#endif


-- ** ttl #attr:ttl#
-- | Specifies the time-to-live value to use in outgoing packets.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingVxlanTtlPropertyInfo             ,
#endif
    constructSettingVxlanTtl                ,
    getSettingVxlanTtl                      ,
    setSettingVxlanTtl                      ,
#if defined(ENABLE_OVERLOADING)
    settingVxlanTtl                         ,
#endif




    ) where

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

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

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

#endif

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

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

foreign import ccall "nm_setting_vxlan_get_type"
    c_nm_setting_vxlan_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingVxlan where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_vxlan_get_type

instance B.Types.GObject SettingVxlan

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSettingVxlanMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSettingVxlanMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSettingVxlanMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSettingVxlanMethod "compare" o = NM.Setting.SettingCompareMethodInfo
    ResolveSettingVxlanMethod "diff" o = NM.Setting.SettingDiffMethodInfo
    ResolveSettingVxlanMethod "duplicate" o = NM.Setting.SettingDuplicateMethodInfo
    ResolveSettingVxlanMethod "enumerateValues" o = NM.Setting.SettingEnumerateValuesMethodInfo
    ResolveSettingVxlanMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSettingVxlanMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSettingVxlanMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSettingVxlanMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSettingVxlanMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSettingVxlanMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSettingVxlanMethod "optionClearByName" o = NM.Setting.SettingOptionClearByNameMethodInfo
    ResolveSettingVxlanMethod "optionGet" o = NM.Setting.SettingOptionGetMethodInfo
    ResolveSettingVxlanMethod "optionGetAllNames" o = NM.Setting.SettingOptionGetAllNamesMethodInfo
    ResolveSettingVxlanMethod "optionGetBoolean" o = NM.Setting.SettingOptionGetBooleanMethodInfo
    ResolveSettingVxlanMethod "optionGetUint32" o = NM.Setting.SettingOptionGetUint32MethodInfo
    ResolveSettingVxlanMethod "optionSet" o = NM.Setting.SettingOptionSetMethodInfo
    ResolveSettingVxlanMethod "optionSetBoolean" o = NM.Setting.SettingOptionSetBooleanMethodInfo
    ResolveSettingVxlanMethod "optionSetUint32" o = NM.Setting.SettingOptionSetUint32MethodInfo
    ResolveSettingVxlanMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSettingVxlanMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSettingVxlanMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSettingVxlanMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSettingVxlanMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSettingVxlanMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSettingVxlanMethod "toString" o = NM.Setting.SettingToStringMethodInfo
    ResolveSettingVxlanMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSettingVxlanMethod "verify" o = NM.Setting.SettingVerifyMethodInfo
    ResolveSettingVxlanMethod "verifySecrets" o = NM.Setting.SettingVerifySecretsMethodInfo
    ResolveSettingVxlanMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSettingVxlanMethod "getAgeing" o = SettingVxlanGetAgeingMethodInfo
    ResolveSettingVxlanMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSettingVxlanMethod "getDbusPropertyType" o = NM.Setting.SettingGetDbusPropertyTypeMethodInfo
    ResolveSettingVxlanMethod "getDestinationPort" o = SettingVxlanGetDestinationPortMethodInfo
    ResolveSettingVxlanMethod "getId" o = SettingVxlanGetIdMethodInfo
    ResolveSettingVxlanMethod "getL2Miss" o = SettingVxlanGetL2MissMethodInfo
    ResolveSettingVxlanMethod "getL3Miss" o = SettingVxlanGetL3MissMethodInfo
    ResolveSettingVxlanMethod "getLearning" o = SettingVxlanGetLearningMethodInfo
    ResolveSettingVxlanMethod "getLimit" o = SettingVxlanGetLimitMethodInfo
    ResolveSettingVxlanMethod "getLocal" o = SettingVxlanGetLocalMethodInfo
    ResolveSettingVxlanMethod "getName" o = NM.Setting.SettingGetNameMethodInfo
    ResolveSettingVxlanMethod "getParent" o = SettingVxlanGetParentMethodInfo
    ResolveSettingVxlanMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingVxlanMethod "getProxy" o = SettingVxlanGetProxyMethodInfo
    ResolveSettingVxlanMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingVxlanMethod "getRemote" o = SettingVxlanGetRemoteMethodInfo
    ResolveSettingVxlanMethod "getRsc" o = SettingVxlanGetRscMethodInfo
    ResolveSettingVxlanMethod "getSecretFlags" o = NM.Setting.SettingGetSecretFlagsMethodInfo
    ResolveSettingVxlanMethod "getSourcePortMax" o = SettingVxlanGetSourcePortMaxMethodInfo
    ResolveSettingVxlanMethod "getSourcePortMin" o = SettingVxlanGetSourcePortMinMethodInfo
    ResolveSettingVxlanMethod "getTos" o = SettingVxlanGetTosMethodInfo
    ResolveSettingVxlanMethod "getTtl" o = SettingVxlanGetTtlMethodInfo
    ResolveSettingVxlanMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingVxlanMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingVxlanMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingVxlanMethod "setSecretFlags" o = NM.Setting.SettingSetSecretFlagsMethodInfo
    ResolveSettingVxlanMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

-- | Set the value of the “@ageing@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #ageing 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanAgeing :: (MonadIO m, IsSettingVxlan o) => o -> Word32 -> m ()
setSettingVxlanAgeing :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Word32 -> m ()
setSettingVxlanAgeing o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"ageing" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@ageing@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanAgeing :: (IsSettingVxlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingVxlanAgeing :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingVxlanAgeing Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"ageing" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanAgeingPropertyInfo
instance AttrInfo SettingVxlanAgeingPropertyInfo where
    type AttrAllowedOps SettingVxlanAgeingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanAgeingPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanAgeingPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingVxlanAgeingPropertyInfo = (~) Word32
    type AttrTransferType SettingVxlanAgeingPropertyInfo = Word32
    type AttrGetType SettingVxlanAgeingPropertyInfo = Word32
    type AttrLabel SettingVxlanAgeingPropertyInfo = "ageing"
    type AttrOrigin SettingVxlanAgeingPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanAgeing
    attrSet = setSettingVxlanAgeing
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanAgeing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.ageing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:ageing"
        })
#endif

-- VVV Prop "destination-port"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@destination-port@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingVxlan #destinationPort
-- @
getSettingVxlanDestinationPort :: (MonadIO m, IsSettingVxlan o) => o -> m Word32
getSettingVxlanDestinationPort :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> m Word32
getSettingVxlanDestinationPort o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"destination-port"

-- | Set the value of the “@destination-port@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #destinationPort 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanDestinationPort :: (MonadIO m, IsSettingVxlan o) => o -> Word32 -> m ()
setSettingVxlanDestinationPort :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Word32 -> m ()
setSettingVxlanDestinationPort o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"destination-port" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@destination-port@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanDestinationPort :: (IsSettingVxlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingVxlanDestinationPort :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingVxlanDestinationPort Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"destination-port" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanDestinationPortPropertyInfo
instance AttrInfo SettingVxlanDestinationPortPropertyInfo where
    type AttrAllowedOps SettingVxlanDestinationPortPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanDestinationPortPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanDestinationPortPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingVxlanDestinationPortPropertyInfo = (~) Word32
    type AttrTransferType SettingVxlanDestinationPortPropertyInfo = Word32
    type AttrGetType SettingVxlanDestinationPortPropertyInfo = Word32
    type AttrLabel SettingVxlanDestinationPortPropertyInfo = "destination-port"
    type AttrOrigin SettingVxlanDestinationPortPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanDestinationPort
    attrSet = setSettingVxlanDestinationPort
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanDestinationPort
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.destinationPort"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:destinationPort"
        })
#endif

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

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

-- | Set the value of the “@id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #id 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanId :: (MonadIO m, IsSettingVxlan o) => o -> Word32 -> m ()
setSettingVxlanId :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Word32 -> m ()
setSettingVxlanId o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"id" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@id@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanId :: (IsSettingVxlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingVxlanId :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingVxlanId Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"id" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanIdPropertyInfo
instance AttrInfo SettingVxlanIdPropertyInfo where
    type AttrAllowedOps SettingVxlanIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanIdPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanIdPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingVxlanIdPropertyInfo = (~) Word32
    type AttrTransferType SettingVxlanIdPropertyInfo = Word32
    type AttrGetType SettingVxlanIdPropertyInfo = Word32
    type AttrLabel SettingVxlanIdPropertyInfo = "id"
    type AttrOrigin SettingVxlanIdPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanId
    attrSet = setSettingVxlanId
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanId
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.id"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:id"
        })
#endif

-- VVV Prop "l2-miss"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@l2-miss@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingVxlan #l2Miss
-- @
getSettingVxlanL2Miss :: (MonadIO m, IsSettingVxlan o) => o -> m Bool
getSettingVxlanL2Miss :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> m Bool
getSettingVxlanL2Miss o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"l2-miss"

-- | Set the value of the “@l2-miss@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #l2Miss 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanL2Miss :: (MonadIO m, IsSettingVxlan o) => o -> Bool -> m ()
setSettingVxlanL2Miss :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Bool -> m ()
setSettingVxlanL2Miss o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"l2-miss" Bool
val

-- | Construct a t'GValueConstruct' with valid value for the “@l2-miss@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanL2Miss :: (IsSettingVxlan o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSettingVxlanL2Miss :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSettingVxlanL2Miss Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"l2-miss" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanL2MissPropertyInfo
instance AttrInfo SettingVxlanL2MissPropertyInfo where
    type AttrAllowedOps SettingVxlanL2MissPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanL2MissPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanL2MissPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingVxlanL2MissPropertyInfo = (~) Bool
    type AttrTransferType SettingVxlanL2MissPropertyInfo = Bool
    type AttrGetType SettingVxlanL2MissPropertyInfo = Bool
    type AttrLabel SettingVxlanL2MissPropertyInfo = "l2-miss"
    type AttrOrigin SettingVxlanL2MissPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanL2Miss
    attrSet = setSettingVxlanL2Miss
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanL2Miss
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.l2Miss"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:l2Miss"
        })
#endif

-- VVV Prop "l3-miss"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@l3-miss@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingVxlan #l3Miss
-- @
getSettingVxlanL3Miss :: (MonadIO m, IsSettingVxlan o) => o -> m Bool
getSettingVxlanL3Miss :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> m Bool
getSettingVxlanL3Miss o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"l3-miss"

-- | Set the value of the “@l3-miss@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #l3Miss 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanL3Miss :: (MonadIO m, IsSettingVxlan o) => o -> Bool -> m ()
setSettingVxlanL3Miss :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Bool -> m ()
setSettingVxlanL3Miss o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"l3-miss" Bool
val

-- | Construct a t'GValueConstruct' with valid value for the “@l3-miss@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanL3Miss :: (IsSettingVxlan o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSettingVxlanL3Miss :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSettingVxlanL3Miss Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"l3-miss" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanL3MissPropertyInfo
instance AttrInfo SettingVxlanL3MissPropertyInfo where
    type AttrAllowedOps SettingVxlanL3MissPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanL3MissPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanL3MissPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingVxlanL3MissPropertyInfo = (~) Bool
    type AttrTransferType SettingVxlanL3MissPropertyInfo = Bool
    type AttrGetType SettingVxlanL3MissPropertyInfo = Bool
    type AttrLabel SettingVxlanL3MissPropertyInfo = "l3-miss"
    type AttrOrigin SettingVxlanL3MissPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanL3Miss
    attrSet = setSettingVxlanL3Miss
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanL3Miss
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.l3Miss"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:l3Miss"
        })
#endif

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

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

-- | Set the value of the “@learning@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #learning 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanLearning :: (MonadIO m, IsSettingVxlan o) => o -> Bool -> m ()
setSettingVxlanLearning :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Bool -> m ()
setSettingVxlanLearning o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"learning" Bool
val

-- | Construct a t'GValueConstruct' with valid value for the “@learning@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanLearning :: (IsSettingVxlan o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSettingVxlanLearning :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSettingVxlanLearning Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"learning" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanLearningPropertyInfo
instance AttrInfo SettingVxlanLearningPropertyInfo where
    type AttrAllowedOps SettingVxlanLearningPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanLearningPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanLearningPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingVxlanLearningPropertyInfo = (~) Bool
    type AttrTransferType SettingVxlanLearningPropertyInfo = Bool
    type AttrGetType SettingVxlanLearningPropertyInfo = Bool
    type AttrLabel SettingVxlanLearningPropertyInfo = "learning"
    type AttrOrigin SettingVxlanLearningPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanLearning
    attrSet = setSettingVxlanLearning
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanLearning
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.learning"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:learning"
        })
#endif

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

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

-- | Set the value of the “@limit@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #limit 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanLimit :: (MonadIO m, IsSettingVxlan o) => o -> Word32 -> m ()
setSettingVxlanLimit :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Word32 -> m ()
setSettingVxlanLimit o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"limit" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@limit@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanLimit :: (IsSettingVxlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingVxlanLimit :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingVxlanLimit Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"limit" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanLimitPropertyInfo
instance AttrInfo SettingVxlanLimitPropertyInfo where
    type AttrAllowedOps SettingVxlanLimitPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanLimitPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanLimitPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingVxlanLimitPropertyInfo = (~) Word32
    type AttrTransferType SettingVxlanLimitPropertyInfo = Word32
    type AttrGetType SettingVxlanLimitPropertyInfo = Word32
    type AttrLabel SettingVxlanLimitPropertyInfo = "limit"
    type AttrOrigin SettingVxlanLimitPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanLimit
    attrSet = setSettingVxlanLimit
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanLimit
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.limit"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:limit"
        })
#endif

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

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

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

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

-- | Set the value of the “@local@” 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' #local
-- @
clearSettingVxlanLocal :: (MonadIO m, IsSettingVxlan o) => o -> m ()
clearSettingVxlanLocal :: forall (m :: * -> *) o. (MonadIO m, IsSettingVxlan o) => o -> m ()
clearSettingVxlanLocal 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
"local" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

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

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

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

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

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

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

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

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

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

-- | Set the value of the “@proxy@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #proxy 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanProxy :: (MonadIO m, IsSettingVxlan o) => o -> Bool -> m ()
setSettingVxlanProxy :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Bool -> m ()
setSettingVxlanProxy o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"proxy" Bool
val

-- | Construct a t'GValueConstruct' with valid value for the “@proxy@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanProxy :: (IsSettingVxlan o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSettingVxlanProxy :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSettingVxlanProxy Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"proxy" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanProxyPropertyInfo
instance AttrInfo SettingVxlanProxyPropertyInfo where
    type AttrAllowedOps SettingVxlanProxyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanProxyPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanProxyPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingVxlanProxyPropertyInfo = (~) Bool
    type AttrTransferType SettingVxlanProxyPropertyInfo = Bool
    type AttrGetType SettingVxlanProxyPropertyInfo = Bool
    type AttrLabel SettingVxlanProxyPropertyInfo = "proxy"
    type AttrOrigin SettingVxlanProxyPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanProxy
    attrSet = setSettingVxlanProxy
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanProxy
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.proxy"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:proxy"
        })
#endif

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

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

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

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

-- | Set the value of the “@remote@” 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' #remote
-- @
clearSettingVxlanRemote :: (MonadIO m, IsSettingVxlan o) => o -> m ()
clearSettingVxlanRemote :: forall (m :: * -> *) o. (MonadIO m, IsSettingVxlan o) => o -> m ()
clearSettingVxlanRemote 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
"remote" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

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

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

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

-- | Set the value of the “@rsc@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #rsc 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanRsc :: (MonadIO m, IsSettingVxlan o) => o -> Bool -> m ()
setSettingVxlanRsc :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Bool -> m ()
setSettingVxlanRsc o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"rsc" Bool
val

-- | Construct a t'GValueConstruct' with valid value for the “@rsc@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanRsc :: (IsSettingVxlan o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSettingVxlanRsc :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSettingVxlanRsc Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"rsc" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanRscPropertyInfo
instance AttrInfo SettingVxlanRscPropertyInfo where
    type AttrAllowedOps SettingVxlanRscPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanRscPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanRscPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingVxlanRscPropertyInfo = (~) Bool
    type AttrTransferType SettingVxlanRscPropertyInfo = Bool
    type AttrGetType SettingVxlanRscPropertyInfo = Bool
    type AttrLabel SettingVxlanRscPropertyInfo = "rsc"
    type AttrOrigin SettingVxlanRscPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanRsc
    attrSet = setSettingVxlanRsc
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanRsc
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.rsc"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:rsc"
        })
#endif

-- VVV Prop "source-port-max"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@source-port-max@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingVxlan #sourcePortMax
-- @
getSettingVxlanSourcePortMax :: (MonadIO m, IsSettingVxlan o) => o -> m Word32
getSettingVxlanSourcePortMax :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> m Word32
getSettingVxlanSourcePortMax o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"source-port-max"

-- | Set the value of the “@source-port-max@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #sourcePortMax 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanSourcePortMax :: (MonadIO m, IsSettingVxlan o) => o -> Word32 -> m ()
setSettingVxlanSourcePortMax :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Word32 -> m ()
setSettingVxlanSourcePortMax o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"source-port-max" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@source-port-max@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanSourcePortMax :: (IsSettingVxlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingVxlanSourcePortMax :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingVxlanSourcePortMax Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"source-port-max" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanSourcePortMaxPropertyInfo
instance AttrInfo SettingVxlanSourcePortMaxPropertyInfo where
    type AttrAllowedOps SettingVxlanSourcePortMaxPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanSourcePortMaxPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanSourcePortMaxPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingVxlanSourcePortMaxPropertyInfo = (~) Word32
    type AttrTransferType SettingVxlanSourcePortMaxPropertyInfo = Word32
    type AttrGetType SettingVxlanSourcePortMaxPropertyInfo = Word32
    type AttrLabel SettingVxlanSourcePortMaxPropertyInfo = "source-port-max"
    type AttrOrigin SettingVxlanSourcePortMaxPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanSourcePortMax
    attrSet = setSettingVxlanSourcePortMax
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanSourcePortMax
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.sourcePortMax"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:sourcePortMax"
        })
#endif

-- VVV Prop "source-port-min"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@source-port-min@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingVxlan #sourcePortMin
-- @
getSettingVxlanSourcePortMin :: (MonadIO m, IsSettingVxlan o) => o -> m Word32
getSettingVxlanSourcePortMin :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> m Word32
getSettingVxlanSourcePortMin o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"source-port-min"

-- | Set the value of the “@source-port-min@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #sourcePortMin 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanSourcePortMin :: (MonadIO m, IsSettingVxlan o) => o -> Word32 -> m ()
setSettingVxlanSourcePortMin :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Word32 -> m ()
setSettingVxlanSourcePortMin o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"source-port-min" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@source-port-min@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanSourcePortMin :: (IsSettingVxlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingVxlanSourcePortMin :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingVxlanSourcePortMin Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"source-port-min" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanSourcePortMinPropertyInfo
instance AttrInfo SettingVxlanSourcePortMinPropertyInfo where
    type AttrAllowedOps SettingVxlanSourcePortMinPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanSourcePortMinPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanSourcePortMinPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingVxlanSourcePortMinPropertyInfo = (~) Word32
    type AttrTransferType SettingVxlanSourcePortMinPropertyInfo = Word32
    type AttrGetType SettingVxlanSourcePortMinPropertyInfo = Word32
    type AttrLabel SettingVxlanSourcePortMinPropertyInfo = "source-port-min"
    type AttrOrigin SettingVxlanSourcePortMinPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanSourcePortMin
    attrSet = setSettingVxlanSourcePortMin
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanSourcePortMin
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.sourcePortMin"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:sourcePortMin"
        })
#endif

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

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

-- | Set the value of the “@tos@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #tos 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanTos :: (MonadIO m, IsSettingVxlan o) => o -> Word32 -> m ()
setSettingVxlanTos :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Word32 -> m ()
setSettingVxlanTos o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"tos" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@tos@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanTos :: (IsSettingVxlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingVxlanTos :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingVxlanTos Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"tos" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanTosPropertyInfo
instance AttrInfo SettingVxlanTosPropertyInfo where
    type AttrAllowedOps SettingVxlanTosPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanTosPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanTosPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingVxlanTosPropertyInfo = (~) Word32
    type AttrTransferType SettingVxlanTosPropertyInfo = Word32
    type AttrGetType SettingVxlanTosPropertyInfo = Word32
    type AttrLabel SettingVxlanTosPropertyInfo = "tos"
    type AttrOrigin SettingVxlanTosPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanTos
    attrSet = setSettingVxlanTos
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanTos
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.tos"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:tos"
        })
#endif

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

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

-- | Set the value of the “@ttl@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingVxlan [ #ttl 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingVxlanTtl :: (MonadIO m, IsSettingVxlan o) => o -> Word32 -> m ()
setSettingVxlanTtl :: forall (m :: * -> *) o.
(MonadIO m, IsSettingVxlan o) =>
o -> Word32 -> m ()
setSettingVxlanTtl o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"ttl" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@ttl@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingVxlanTtl :: (IsSettingVxlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingVxlanTtl :: forall o (m :: * -> *).
(IsSettingVxlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingVxlanTtl Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"ttl" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingVxlanTtlPropertyInfo
instance AttrInfo SettingVxlanTtlPropertyInfo where
    type AttrAllowedOps SettingVxlanTtlPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingVxlanTtlPropertyInfo = IsSettingVxlan
    type AttrSetTypeConstraint SettingVxlanTtlPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingVxlanTtlPropertyInfo = (~) Word32
    type AttrTransferType SettingVxlanTtlPropertyInfo = Word32
    type AttrGetType SettingVxlanTtlPropertyInfo = Word32
    type AttrLabel SettingVxlanTtlPropertyInfo = "ttl"
    type AttrOrigin SettingVxlanTtlPropertyInfo = SettingVxlan
    attrGet = getSettingVxlanTtl
    attrSet = setSettingVxlanTtl
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingVxlanTtl
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingVxlan.ttl"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingVxlan.html#g:attr:ttl"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingVxlan
type instance O.AttributeList SettingVxlan = SettingVxlanAttributeList
type SettingVxlanAttributeList = ('[ '("ageing", SettingVxlanAgeingPropertyInfo), '("destinationPort", SettingVxlanDestinationPortPropertyInfo), '("id", SettingVxlanIdPropertyInfo), '("l2Miss", SettingVxlanL2MissPropertyInfo), '("l3Miss", SettingVxlanL3MissPropertyInfo), '("learning", SettingVxlanLearningPropertyInfo), '("limit", SettingVxlanLimitPropertyInfo), '("local", SettingVxlanLocalPropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("parent", SettingVxlanParentPropertyInfo), '("proxy", SettingVxlanProxyPropertyInfo), '("remote", SettingVxlanRemotePropertyInfo), '("rsc", SettingVxlanRscPropertyInfo), '("sourcePortMax", SettingVxlanSourcePortMaxPropertyInfo), '("sourcePortMin", SettingVxlanSourcePortMinPropertyInfo), '("tos", SettingVxlanTosPropertyInfo), '("ttl", SettingVxlanTtlPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingVxlanAgeing :: AttrLabelProxy "ageing"
settingVxlanAgeing = AttrLabelProxy

settingVxlanDestinationPort :: AttrLabelProxy "destinationPort"
settingVxlanDestinationPort = AttrLabelProxy

settingVxlanId :: AttrLabelProxy "id"
settingVxlanId = AttrLabelProxy

settingVxlanL2Miss :: AttrLabelProxy "l2Miss"
settingVxlanL2Miss = AttrLabelProxy

settingVxlanL3Miss :: AttrLabelProxy "l3Miss"
settingVxlanL3Miss = AttrLabelProxy

settingVxlanLearning :: AttrLabelProxy "learning"
settingVxlanLearning = AttrLabelProxy

settingVxlanLimit :: AttrLabelProxy "limit"
settingVxlanLimit = AttrLabelProxy

settingVxlanLocal :: AttrLabelProxy "local"
settingVxlanLocal = AttrLabelProxy

settingVxlanParent :: AttrLabelProxy "parent"
settingVxlanParent = AttrLabelProxy

settingVxlanProxy :: AttrLabelProxy "proxy"
settingVxlanProxy = AttrLabelProxy

settingVxlanRemote :: AttrLabelProxy "remote"
settingVxlanRemote = AttrLabelProxy

settingVxlanRsc :: AttrLabelProxy "rsc"
settingVxlanRsc = AttrLabelProxy

settingVxlanSourcePortMax :: AttrLabelProxy "sourcePortMax"
settingVxlanSourcePortMax = AttrLabelProxy

settingVxlanSourcePortMin :: AttrLabelProxy "sourcePortMin"
settingVxlanSourcePortMin = AttrLabelProxy

settingVxlanTos :: AttrLabelProxy "tos"
settingVxlanTos = AttrLabelProxy

settingVxlanTtl :: AttrLabelProxy "ttl"
settingVxlanTtl = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "nm_setting_vxlan_new" nm_setting_vxlan_new :: 
    IO (Ptr SettingVxlan)

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

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetAgeing ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Word32
    -- ^ __Returns:__ the [SettingVxlan:ageing]("GI.NM.Objects.SettingVxlan#g:attr:ageing") property of the setting
settingVxlanGetAgeing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Word32
settingVxlanGetAgeing a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingVxlan -> IO Word32
nm_setting_vxlan_get_ageing Ptr SettingVxlan
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetAgeingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetAgeingMethodInfo a signature where
    overloadedMethod = settingVxlanGetAgeing

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


#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetDestinationPort ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Word32
    -- ^ __Returns:__ the [SettingVxlan:destinationPort]("GI.NM.Objects.SettingVxlan#g:attr:destinationPort") property of the setting
settingVxlanGetDestinationPort :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Word32
settingVxlanGetDestinationPort a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingVxlan -> IO Word32
nm_setting_vxlan_get_destination_port Ptr SettingVxlan
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetDestinationPortMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetDestinationPortMethodInfo a signature where
    overloadedMethod = settingVxlanGetDestinationPort

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


#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetId ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Word32
    -- ^ __Returns:__ the [SettingVxlan:id]("GI.NM.Objects.SettingVxlan#g:attr:id") property of the setting
settingVxlanGetId :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Word32
settingVxlanGetId a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingVxlan -> IO Word32
nm_setting_vxlan_get_id Ptr SettingVxlan
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetIdMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetIdMethodInfo a signature where
    overloadedMethod = settingVxlanGetId

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


#endif

-- method SettingVxlan::get_l2_miss
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingVxlan" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingVxlan"
--                 , 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_vxlan_get_l2_miss" nm_setting_vxlan_get_l2_miss :: 
    Ptr SettingVxlan ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingVxlan"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetL2Miss ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Bool
    -- ^ __Returns:__ the t'GI.NM.Objects.SettingVxlan.SettingVxlan':@/l2_miss/@ property of the setting
settingVxlanGetL2Miss :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Bool
settingVxlanGetL2Miss a
setting = 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 SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingVxlan -> IO CInt
nm_setting_vxlan_get_l2_miss Ptr SettingVxlan
setting'
    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
setting
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetL2MissMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetL2MissMethodInfo a signature where
    overloadedMethod = settingVxlanGetL2Miss

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


#endif

-- method SettingVxlan::get_l3_miss
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingVxlan" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingVxlan"
--                 , 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_vxlan_get_l3_miss" nm_setting_vxlan_get_l3_miss :: 
    Ptr SettingVxlan ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingVxlan"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetL3Miss ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Bool
    -- ^ __Returns:__ the t'GI.NM.Objects.SettingVxlan.SettingVxlan':@/l3_miss/@ property of the setting
settingVxlanGetL3Miss :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Bool
settingVxlanGetL3Miss a
setting = 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 SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingVxlan -> IO CInt
nm_setting_vxlan_get_l3_miss Ptr SettingVxlan
setting'
    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
setting
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetL3MissMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetL3MissMethodInfo a signature where
    overloadedMethod = settingVxlanGetL3Miss

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


#endif

-- method SettingVxlan::get_learning
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingVxlan" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingVxlan"
--                 , 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_vxlan_get_learning" nm_setting_vxlan_get_learning :: 
    Ptr SettingVxlan ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingVxlan"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetLearning ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Bool
    -- ^ __Returns:__ the [SettingVxlan:learning]("GI.NM.Objects.SettingVxlan#g:attr:learning") property of the setting
settingVxlanGetLearning :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Bool
settingVxlanGetLearning a
setting = 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 SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingVxlan -> IO CInt
nm_setting_vxlan_get_learning Ptr SettingVxlan
setting'
    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
setting
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetLearningMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetLearningMethodInfo a signature where
    overloadedMethod = settingVxlanGetLearning

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


#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetLimit ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Word32
    -- ^ __Returns:__ the [SettingVxlan:limit]("GI.NM.Objects.SettingVxlan#g:attr:limit") property of the setting
settingVxlanGetLimit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Word32
settingVxlanGetLimit a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingVxlan -> IO Word32
nm_setting_vxlan_get_limit Ptr SettingVxlan
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetLimitMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetLimitMethodInfo a signature where
    overloadedMethod = settingVxlanGetLimit

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m T.Text
    -- ^ __Returns:__ the [SettingVxlan:local]("GI.NM.Objects.SettingVxlan#g:attr:local") property of the setting
settingVxlanGetLocal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Text
settingVxlanGetLocal 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 SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingVxlan -> IO CString
nm_setting_vxlan_get_local Ptr SettingVxlan
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingVxlanGetLocal" 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 SettingVxlanGetLocalMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetLocalMethodInfo a signature where
    overloadedMethod = settingVxlanGetLocal

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m T.Text
    -- ^ __Returns:__ the [SettingVxlan:parent]("GI.NM.Objects.SettingVxlan#g:attr:parent") property of the setting
settingVxlanGetParent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Text
settingVxlanGetParent 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 SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingVxlan -> IO CString
nm_setting_vxlan_get_parent Ptr SettingVxlan
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingVxlanGetParent" 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 SettingVxlanGetParentMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetParentMethodInfo a signature where
    overloadedMethod = settingVxlanGetParent

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


#endif

-- method SettingVxlan::get_proxy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingVxlan" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingVxlan"
--                 , 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_vxlan_get_proxy" nm_setting_vxlan_get_proxy :: 
    Ptr SettingVxlan ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingVxlan"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetProxy ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Bool
    -- ^ __Returns:__ the [SettingVxlan:proxy]("GI.NM.Objects.SettingVxlan#g:attr:proxy") property of the setting
settingVxlanGetProxy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Bool
settingVxlanGetProxy a
setting = 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 SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingVxlan -> IO CInt
nm_setting_vxlan_get_proxy Ptr SettingVxlan
setting'
    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
setting
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetProxyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetProxyMethodInfo a signature where
    overloadedMethod = settingVxlanGetProxy

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetRemote ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m T.Text
    -- ^ __Returns:__ the [SettingVxlan:remote]("GI.NM.Objects.SettingVxlan#g:attr:remote") property of the setting
settingVxlanGetRemote :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Text
settingVxlanGetRemote 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 SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingVxlan -> IO CString
nm_setting_vxlan_get_remote Ptr SettingVxlan
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingVxlanGetRemote" 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 SettingVxlanGetRemoteMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetRemoteMethodInfo a signature where
    overloadedMethod = settingVxlanGetRemote

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


#endif

-- method SettingVxlan::get_rsc
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingVxlan" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingVxlan"
--                 , 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_vxlan_get_rsc" nm_setting_vxlan_get_rsc :: 
    Ptr SettingVxlan ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingVxlan"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetRsc ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Bool
    -- ^ __Returns:__ the [SettingVxlan:rsc]("GI.NM.Objects.SettingVxlan#g:attr:rsc") property of the setting
settingVxlanGetRsc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Bool
settingVxlanGetRsc a
setting = 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 SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingVxlan -> IO CInt
nm_setting_vxlan_get_rsc Ptr SettingVxlan
setting'
    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
setting
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetRscMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetRscMethodInfo a signature where
    overloadedMethod = settingVxlanGetRsc

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


#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetSourcePortMax ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Word32
    -- ^ __Returns:__ the [SettingVxlan:sourcePortMax]("GI.NM.Objects.SettingVxlan#g:attr:sourcePortMax") property of the setting
settingVxlanGetSourcePortMax :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Word32
settingVxlanGetSourcePortMax a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingVxlan -> IO Word32
nm_setting_vxlan_get_source_port_max Ptr SettingVxlan
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetSourcePortMaxMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetSourcePortMaxMethodInfo a signature where
    overloadedMethod = settingVxlanGetSourcePortMax

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


#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetSourcePortMin ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Word32
    -- ^ __Returns:__ the [SettingVxlan:sourcePortMin]("GI.NM.Objects.SettingVxlan#g:attr:sourcePortMin") property of the setting
settingVxlanGetSourcePortMin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Word32
settingVxlanGetSourcePortMin a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingVxlan -> IO Word32
nm_setting_vxlan_get_source_port_min Ptr SettingVxlan
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetSourcePortMinMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetSourcePortMinMethodInfo a signature where
    overloadedMethod = settingVxlanGetSourcePortMin

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


#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetTos ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Word32
    -- ^ __Returns:__ the [SettingVxlan:tos]("GI.NM.Objects.SettingVxlan#g:attr:tos") property of the setting
settingVxlanGetTos :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Word32
settingVxlanGetTos a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingVxlan -> IO Word32
nm_setting_vxlan_get_tos Ptr SettingVxlan
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetTosMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetTosMethodInfo a signature where
    overloadedMethod = settingVxlanGetTos

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


#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingVxlanGetTtl ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingVxlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingVxlan.SettingVxlan'
    -> m Word32
    -- ^ __Returns:__ the [SettingVxlan:ttl]("GI.NM.Objects.SettingVxlan#g:attr:ttl") property of the setting
settingVxlanGetTtl :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingVxlan a) =>
a -> m Word32
settingVxlanGetTtl a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingVxlan
setting' <- a -> IO (Ptr SettingVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingVxlan -> IO Word32
nm_setting_vxlan_get_ttl Ptr SettingVxlan
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingVxlanGetTtlMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingVxlan a) => O.OverloadedMethod SettingVxlanGetTtlMethodInfo a signature where
    overloadedMethod = settingVxlanGetTtl

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


#endif