{-# LANGUAGE TypeApplications #-}


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

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

module GI.NM.Objects.SettingIPTunnel
    ( 

-- * Exported types
    SettingIPTunnel(..)                     ,
    IsSettingIPTunnel                       ,
    toSettingIPTunnel                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [compare]("GI.NM.Objects.Setting#g:method:compare"), [diff]("GI.NM.Objects.Setting#g:method:diff"), [duplicate]("GI.NM.Objects.Setting#g:method:duplicate"), [enumerateValues]("GI.NM.Objects.Setting#g:method:enumerateValues"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [optionClearByName]("GI.NM.Objects.Setting#g:method:optionClearByName"), [optionGet]("GI.NM.Objects.Setting#g:method:optionGet"), [optionGetAllNames]("GI.NM.Objects.Setting#g:method:optionGetAllNames"), [optionGetBoolean]("GI.NM.Objects.Setting#g:method:optionGetBoolean"), [optionGetUint32]("GI.NM.Objects.Setting#g:method:optionGetUint32"), [optionSet]("GI.NM.Objects.Setting#g:method:optionSet"), [optionSetBoolean]("GI.NM.Objects.Setting#g:method:optionSetBoolean"), [optionSetUint32]("GI.NM.Objects.Setting#g:method:optionSetUint32"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.NM.Objects.Setting#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [verify]("GI.NM.Objects.Setting#g:method:verify"), [verifySecrets]("GI.NM.Objects.Setting#g:method:verifySecrets"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDbusPropertyType]("GI.NM.Objects.Setting#g:method:getDbusPropertyType"), [getEncapsulationLimit]("GI.NM.Objects.SettingIPTunnel#g:method:getEncapsulationLimit"), [getFlags]("GI.NM.Objects.SettingIPTunnel#g:method:getFlags"), [getFlowLabel]("GI.NM.Objects.SettingIPTunnel#g:method:getFlowLabel"), [getFwmark]("GI.NM.Objects.SettingIPTunnel#g:method:getFwmark"), [getInputKey]("GI.NM.Objects.SettingIPTunnel#g:method:getInputKey"), [getLocal]("GI.NM.Objects.SettingIPTunnel#g:method:getLocal"), [getMode]("GI.NM.Objects.SettingIPTunnel#g:method:getMode"), [getMtu]("GI.NM.Objects.SettingIPTunnel#g:method:getMtu"), [getName]("GI.NM.Objects.Setting#g:method:getName"), [getOutputKey]("GI.NM.Objects.SettingIPTunnel#g:method:getOutputKey"), [getParent]("GI.NM.Objects.SettingIPTunnel#g:method:getParent"), [getPathMtuDiscovery]("GI.NM.Objects.SettingIPTunnel#g:method:getPathMtuDiscovery"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRemote]("GI.NM.Objects.SettingIPTunnel#g:method:getRemote"), [getSecretFlags]("GI.NM.Objects.Setting#g:method:getSecretFlags"), [getTos]("GI.NM.Objects.SettingIPTunnel#g:method:getTos"), [getTtl]("GI.NM.Objects.SettingIPTunnel#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)
    ResolveSettingIPTunnelMethod            ,
#endif

-- ** getEncapsulationLimit #method:getEncapsulationLimit#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetEncapsulationLimitMethodInfo,
#endif
    settingIPTunnelGetEncapsulationLimit    ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetFlagsMethodInfo       ,
#endif
    settingIPTunnelGetFlags                 ,


-- ** getFlowLabel #method:getFlowLabel#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetFlowLabelMethodInfo   ,
#endif
    settingIPTunnelGetFlowLabel             ,


-- ** getFwmark #method:getFwmark#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetFwmarkMethodInfo      ,
#endif
    settingIPTunnelGetFwmark                ,


-- ** getInputKey #method:getInputKey#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetInputKeyMethodInfo    ,
#endif
    settingIPTunnelGetInputKey              ,


-- ** getLocal #method:getLocal#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetLocalMethodInfo       ,
#endif
    settingIPTunnelGetLocal                 ,


-- ** getMode #method:getMode#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetModeMethodInfo        ,
#endif
    settingIPTunnelGetMode                  ,


-- ** getMtu #method:getMtu#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetMtuMethodInfo         ,
#endif
    settingIPTunnelGetMtu                   ,


-- ** getOutputKey #method:getOutputKey#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetOutputKeyMethodInfo   ,
#endif
    settingIPTunnelGetOutputKey             ,


-- ** getParent #method:getParent#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetParentMethodInfo      ,
#endif
    settingIPTunnelGetParent                ,


-- ** getPathMtuDiscovery #method:getPathMtuDiscovery#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetPathMtuDiscoveryMethodInfo,
#endif
    settingIPTunnelGetPathMtuDiscovery      ,


-- ** getRemote #method:getRemote#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetRemoteMethodInfo      ,
#endif
    settingIPTunnelGetRemote                ,


-- ** getTos #method:getTos#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetTosMethodInfo         ,
#endif
    settingIPTunnelGetTos                   ,


-- ** getTtl #method:getTtl#

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelGetTtlMethodInfo         ,
#endif
    settingIPTunnelGetTtl                   ,


-- ** new #method:new#

    settingIPTunnelNew                      ,




 -- * Properties


-- ** encapsulationLimit #attr:encapsulationLimit#
-- | How many additional levels of encapsulation are permitted to be prepended
-- to packets. This property applies only to IPv6 tunnels. To disable this option,
-- add 'GI.NM.Flags.IPTunnelFlagsIp6IgnEncapLimit' to ip-tunnel flags.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelEncapsulationLimitPropertyInfo,
#endif
    constructSettingIPTunnelEncapsulationLimit,
    getSettingIPTunnelEncapsulationLimit    ,
    setSettingIPTunnelEncapsulationLimit    ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelEncapsulationLimit       ,
#endif


-- ** flags #attr:flags#
-- | Tunnel flags. Currently, the following values are supported:
-- 'GI.NM.Flags.IPTunnelFlagsIp6IgnEncapLimit', 'GI.NM.Flags.IPTunnelFlagsIp6UseOrigTclass',
-- 'GI.NM.Flags.IPTunnelFlagsIp6UseOrigFlowlabel', 'GI.NM.Flags.IPTunnelFlagsIp6Mip6Dev',
-- 'GI.NM.Flags.IPTunnelFlagsIp6RcvDscpCopy', 'GI.NM.Flags.IPTunnelFlagsIp6UseOrigFwmark'.
-- They are valid only for IPv6 tunnels.
-- 
-- /Since: 1.12/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelFlagsPropertyInfo        ,
#endif
    constructSettingIPTunnelFlags           ,
    getSettingIPTunnelFlags                 ,
    setSettingIPTunnelFlags                 ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelFlags                    ,
#endif


-- ** flowLabel #attr:flowLabel#
-- | The flow label to assign to tunnel packets. This property applies only to
-- IPv6 tunnels.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelFlowLabelPropertyInfo    ,
#endif
    constructSettingIPTunnelFlowLabel       ,
    getSettingIPTunnelFlowLabel             ,
    setSettingIPTunnelFlowLabel             ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelFlowLabel                ,
#endif


-- ** fwmark #attr:fwmark#
-- | The fwmark value to assign to tunnel packets. This property can be set
-- to a non zero value only on VTI and VTI6 tunnels.
-- 
-- /Since: 1.42/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelFwmarkPropertyInfo       ,
#endif
    constructSettingIPTunnelFwmark          ,
    getSettingIPTunnelFwmark                ,
    setSettingIPTunnelFwmark                ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelFwmark                   ,
#endif


-- ** inputKey #attr:inputKey#
-- | The key used for tunnel input packets; the property is valid only for
-- certain tunnel modes (GRE, IP6GRE). If empty, no key is used.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelInputKeyPropertyInfo     ,
#endif
    clearSettingIPTunnelInputKey            ,
    constructSettingIPTunnelInputKey        ,
    getSettingIPTunnelInputKey              ,
    setSettingIPTunnelInputKey              ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelInputKey                 ,
#endif


-- ** local #attr:local#
-- | The local endpoint of the tunnel; the value can be empty, otherwise it
-- must contain an IPv4 or IPv6 address.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelLocalPropertyInfo        ,
#endif
    clearSettingIPTunnelLocal               ,
    constructSettingIPTunnelLocal           ,
    getSettingIPTunnelLocal                 ,
    setSettingIPTunnelLocal                 ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelLocal                    ,
#endif


-- ** mode #attr:mode#
-- | The tunneling mode. Valid values: 'GI.NM.Enums.IPTunnelModeIpip',
-- 'GI.NM.Enums.IPTunnelModeGre', 'GI.NM.Enums.IPTunnelModeSit', 'GI.NM.Enums.IPTunnelModeIsatap',
-- 'GI.NM.Enums.IPTunnelModeVti', 'GI.NM.Enums.IPTunnelModeIp6ip6', 'GI.NM.Enums.IPTunnelModeIpip6',
-- 'GI.NM.Enums.IPTunnelModeIp6gre', 'GI.NM.Enums.IPTunnelModeVti6', 'GI.NM.Enums.IPTunnelModeGretap'
-- and 'GI.NM.Enums.IPTunnelModeIp6gretap'
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelModePropertyInfo         ,
#endif
    constructSettingIPTunnelMode            ,
    getSettingIPTunnelMode                  ,
    setSettingIPTunnelMode                  ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelMode                     ,
#endif


-- ** mtu #attr:mtu#
-- | If non-zero, only transmit packets of the specified size or smaller,
-- breaking larger packets up into multiple fragments.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelMtuPropertyInfo          ,
#endif
    constructSettingIPTunnelMtu             ,
    getSettingIPTunnelMtu                   ,
    setSettingIPTunnelMtu                   ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelMtu                      ,
#endif


-- ** outputKey #attr:outputKey#
-- | The key used for tunnel output packets; the property is valid only for
-- certain tunnel modes (GRE, IP6GRE). If empty, no key is used.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelOutputKeyPropertyInfo    ,
#endif
    clearSettingIPTunnelOutputKey           ,
    constructSettingIPTunnelOutputKey       ,
    getSettingIPTunnelOutputKey             ,
    setSettingIPTunnelOutputKey             ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelOutputKey                ,
#endif


-- ** parent #attr:parent#
-- | If given, specifies the parent interface name or parent connection UUID
-- the new device will be bound to so that tunneled packets will only be
-- routed via that interface.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelParentPropertyInfo       ,
#endif
    clearSettingIPTunnelParent              ,
    constructSettingIPTunnelParent          ,
    getSettingIPTunnelParent                ,
    setSettingIPTunnelParent                ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelParent                   ,
#endif


-- ** pathMtuDiscovery #attr:pathMtuDiscovery#
-- | Whether to enable Path MTU Discovery on this tunnel.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelPathMtuDiscoveryPropertyInfo,
#endif
    constructSettingIPTunnelPathMtuDiscovery,
    getSettingIPTunnelPathMtuDiscovery      ,
    setSettingIPTunnelPathMtuDiscovery      ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelPathMtuDiscovery         ,
#endif


-- ** remote #attr:remote#
-- | The remote endpoint of the tunnel; the value must contain an IPv4 or IPv6
-- address.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelRemotePropertyInfo       ,
#endif
    clearSettingIPTunnelRemote              ,
    constructSettingIPTunnelRemote          ,
    getSettingIPTunnelRemote                ,
    setSettingIPTunnelRemote                ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelRemote                   ,
#endif


-- ** tos #attr:tos#
-- | The type of service (IPv4) or traffic class (IPv6) field to be set on
-- tunneled packets.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelTosPropertyInfo          ,
#endif
    constructSettingIPTunnelTos             ,
    getSettingIPTunnelTos                   ,
    setSettingIPTunnelTos                   ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelTos                      ,
#endif


-- ** ttl #attr:ttl#
-- | The TTL to assign to tunneled packets. 0 is a special value meaning that
-- packets inherit the TTL value.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingIPTunnelTtlPropertyInfo          ,
#endif
    constructSettingIPTunnelTtl             ,
    getSettingIPTunnelTtl                   ,
    setSettingIPTunnelTtl                   ,
#if defined(ENABLE_OVERLOADING)
    settingIPTunnelTtl                      ,
#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.SettingInfiniband as NM.SettingInfiniband
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacsec as NM.SettingMacsec
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacvlan as NM.SettingMacvlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOlpcMesh as NM.SettingOlpcMesh
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsBridge as NM.SettingOvsBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsInterface as NM.SettingOvsInterface
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPatch as NM.SettingOvsPatch
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPort as NM.SettingOvsPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPpp as NM.SettingPpp
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPppoe as NM.SettingPppoe
import {-# SOURCE #-} qualified GI.NM.Objects.SettingProxy as NM.SettingProxy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingSerial as NM.SettingSerial
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTCConfig as NM.SettingTCConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeam as NM.SettingTeam
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeamPort as NM.SettingTeamPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTun as NM.SettingTun
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVlan as NM.SettingVlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVpn as NM.SettingVpn
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVxlan as NM.SettingVxlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWimax as NM.SettingWimax
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWired as NM.SettingWired
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWireless as NM.SettingWireless
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWirelessSecurity as NM.SettingWirelessSecurity
import {-# SOURCE #-} qualified GI.NM.Structs.BridgeVlan as NM.BridgeVlan
import {-# SOURCE #-} qualified GI.NM.Structs.IPAddress as NM.IPAddress
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoute as NM.IPRoute
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoutingRule as NM.IPRoutingRule
import {-# SOURCE #-} qualified GI.NM.Structs.Range as NM.Range
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec

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

#endif

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

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

foreign import ccall "nm_setting_ip_tunnel_get_type"
    c_nm_setting_ip_tunnel_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingIPTunnel where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_ip_tunnel_get_type

instance B.Types.GObject SettingIPTunnel

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSettingIPTunnelMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSettingIPTunnelMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSettingIPTunnelMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSettingIPTunnelMethod "compare" o = NM.Setting.SettingCompareMethodInfo
    ResolveSettingIPTunnelMethod "diff" o = NM.Setting.SettingDiffMethodInfo
    ResolveSettingIPTunnelMethod "duplicate" o = NM.Setting.SettingDuplicateMethodInfo
    ResolveSettingIPTunnelMethod "enumerateValues" o = NM.Setting.SettingEnumerateValuesMethodInfo
    ResolveSettingIPTunnelMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSettingIPTunnelMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSettingIPTunnelMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSettingIPTunnelMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSettingIPTunnelMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSettingIPTunnelMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSettingIPTunnelMethod "optionClearByName" o = NM.Setting.SettingOptionClearByNameMethodInfo
    ResolveSettingIPTunnelMethod "optionGet" o = NM.Setting.SettingOptionGetMethodInfo
    ResolveSettingIPTunnelMethod "optionGetAllNames" o = NM.Setting.SettingOptionGetAllNamesMethodInfo
    ResolveSettingIPTunnelMethod "optionGetBoolean" o = NM.Setting.SettingOptionGetBooleanMethodInfo
    ResolveSettingIPTunnelMethod "optionGetUint32" o = NM.Setting.SettingOptionGetUint32MethodInfo
    ResolveSettingIPTunnelMethod "optionSet" o = NM.Setting.SettingOptionSetMethodInfo
    ResolveSettingIPTunnelMethod "optionSetBoolean" o = NM.Setting.SettingOptionSetBooleanMethodInfo
    ResolveSettingIPTunnelMethod "optionSetUint32" o = NM.Setting.SettingOptionSetUint32MethodInfo
    ResolveSettingIPTunnelMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSettingIPTunnelMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSettingIPTunnelMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSettingIPTunnelMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSettingIPTunnelMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSettingIPTunnelMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSettingIPTunnelMethod "toString" o = NM.Setting.SettingToStringMethodInfo
    ResolveSettingIPTunnelMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSettingIPTunnelMethod "verify" o = NM.Setting.SettingVerifyMethodInfo
    ResolveSettingIPTunnelMethod "verifySecrets" o = NM.Setting.SettingVerifySecretsMethodInfo
    ResolveSettingIPTunnelMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSettingIPTunnelMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSettingIPTunnelMethod "getDbusPropertyType" o = NM.Setting.SettingGetDbusPropertyTypeMethodInfo
    ResolveSettingIPTunnelMethod "getEncapsulationLimit" o = SettingIPTunnelGetEncapsulationLimitMethodInfo
    ResolveSettingIPTunnelMethod "getFlags" o = SettingIPTunnelGetFlagsMethodInfo
    ResolveSettingIPTunnelMethod "getFlowLabel" o = SettingIPTunnelGetFlowLabelMethodInfo
    ResolveSettingIPTunnelMethod "getFwmark" o = SettingIPTunnelGetFwmarkMethodInfo
    ResolveSettingIPTunnelMethod "getInputKey" o = SettingIPTunnelGetInputKeyMethodInfo
    ResolveSettingIPTunnelMethod "getLocal" o = SettingIPTunnelGetLocalMethodInfo
    ResolveSettingIPTunnelMethod "getMode" o = SettingIPTunnelGetModeMethodInfo
    ResolveSettingIPTunnelMethod "getMtu" o = SettingIPTunnelGetMtuMethodInfo
    ResolveSettingIPTunnelMethod "getName" o = NM.Setting.SettingGetNameMethodInfo
    ResolveSettingIPTunnelMethod "getOutputKey" o = SettingIPTunnelGetOutputKeyMethodInfo
    ResolveSettingIPTunnelMethod "getParent" o = SettingIPTunnelGetParentMethodInfo
    ResolveSettingIPTunnelMethod "getPathMtuDiscovery" o = SettingIPTunnelGetPathMtuDiscoveryMethodInfo
    ResolveSettingIPTunnelMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingIPTunnelMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingIPTunnelMethod "getRemote" o = SettingIPTunnelGetRemoteMethodInfo
    ResolveSettingIPTunnelMethod "getSecretFlags" o = NM.Setting.SettingGetSecretFlagsMethodInfo
    ResolveSettingIPTunnelMethod "getTos" o = SettingIPTunnelGetTosMethodInfo
    ResolveSettingIPTunnelMethod "getTtl" o = SettingIPTunnelGetTtlMethodInfo
    ResolveSettingIPTunnelMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingIPTunnelMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingIPTunnelMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingIPTunnelMethod "setSecretFlags" o = NM.Setting.SettingSetSecretFlagsMethodInfo
    ResolveSettingIPTunnelMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

-- | Get the value of the “@encapsulation-limit@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingIPTunnel #encapsulationLimit
-- @
getSettingIPTunnelEncapsulationLimit :: (MonadIO m, IsSettingIPTunnel o) => o -> m Word32
getSettingIPTunnelEncapsulationLimit :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m Word32
getSettingIPTunnelEncapsulationLimit 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
"encapsulation-limit"

-- | Set the value of the “@encapsulation-limit@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingIPTunnel [ #encapsulationLimit 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelEncapsulationLimit :: (MonadIO m, IsSettingIPTunnel o) => o -> Word32 -> m ()
setSettingIPTunnelEncapsulationLimit :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Word32 -> m ()
setSettingIPTunnelEncapsulationLimit 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
"encapsulation-limit" Word32
val

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

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

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

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

-- | Set the value of the “@flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingIPTunnel [ #flags 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelFlags :: (MonadIO m, IsSettingIPTunnel o) => o -> Word32 -> m ()
setSettingIPTunnelFlags :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Word32 -> m ()
setSettingIPTunnelFlags 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
"flags" Word32
val

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

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

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

-- | Get the value of the “@flow-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingIPTunnel #flowLabel
-- @
getSettingIPTunnelFlowLabel :: (MonadIO m, IsSettingIPTunnel o) => o -> m Word32
getSettingIPTunnelFlowLabel :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m Word32
getSettingIPTunnelFlowLabel 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
"flow-label"

-- | Set the value of the “@flow-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingIPTunnel [ #flowLabel 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelFlowLabel :: (MonadIO m, IsSettingIPTunnel o) => o -> Word32 -> m ()
setSettingIPTunnelFlowLabel :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Word32 -> m ()
setSettingIPTunnelFlowLabel 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
"flow-label" Word32
val

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

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

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

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

-- | Set the value of the “@fwmark@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingIPTunnel [ #fwmark 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelFwmark :: (MonadIO m, IsSettingIPTunnel o) => o -> Word32 -> m ()
setSettingIPTunnelFwmark :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Word32 -> m ()
setSettingIPTunnelFwmark 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
"fwmark" Word32
val

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

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

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data SettingIPTunnelInputKeyPropertyInfo
instance AttrInfo SettingIPTunnelInputKeyPropertyInfo where
    type AttrAllowedOps SettingIPTunnelInputKeyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingIPTunnelInputKeyPropertyInfo = IsSettingIPTunnel
    type AttrSetTypeConstraint SettingIPTunnelInputKeyPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingIPTunnelInputKeyPropertyInfo = (~) T.Text
    type AttrTransferType SettingIPTunnelInputKeyPropertyInfo = T.Text
    type AttrGetType SettingIPTunnelInputKeyPropertyInfo = T.Text
    type AttrLabel SettingIPTunnelInputKeyPropertyInfo = "input-key"
    type AttrOrigin SettingIPTunnelInputKeyPropertyInfo = SettingIPTunnel
    attrGet = getSettingIPTunnelInputKey
    attrSet = setSettingIPTunnelInputKey
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIPTunnelInputKey
    attrClear = clearSettingIPTunnelInputKey
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIPTunnel.inputKey"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIPTunnel.html#g:attr:inputKey"
        })
#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' settingIPTunnel #local
-- @
getSettingIPTunnelLocal :: (MonadIO m, IsSettingIPTunnel o) => o -> m T.Text
getSettingIPTunnelLocal :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m Text
getSettingIPTunnelLocal 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
"getSettingIPTunnelLocal" (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' settingIPTunnel [ #local 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelLocal :: (MonadIO m, IsSettingIPTunnel o) => o -> T.Text -> m ()
setSettingIPTunnelLocal :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Text -> m ()
setSettingIPTunnelLocal 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`.
constructSettingIPTunnelLocal :: (IsSettingIPTunnel o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingIPTunnelLocal :: forall o (m :: * -> *).
(IsSettingIPTunnel o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingIPTunnelLocal 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
-- @
clearSettingIPTunnelLocal :: (MonadIO m, IsSettingIPTunnel o) => o -> m ()
clearSettingIPTunnelLocal :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m ()
clearSettingIPTunnelLocal 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 SettingIPTunnelLocalPropertyInfo
instance AttrInfo SettingIPTunnelLocalPropertyInfo where
    type AttrAllowedOps SettingIPTunnelLocalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingIPTunnelLocalPropertyInfo = IsSettingIPTunnel
    type AttrSetTypeConstraint SettingIPTunnelLocalPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingIPTunnelLocalPropertyInfo = (~) T.Text
    type AttrTransferType SettingIPTunnelLocalPropertyInfo = T.Text
    type AttrGetType SettingIPTunnelLocalPropertyInfo = T.Text
    type AttrLabel SettingIPTunnelLocalPropertyInfo = "local"
    type AttrOrigin SettingIPTunnelLocalPropertyInfo = SettingIPTunnel
    attrGet = getSettingIPTunnelLocal
    attrSet = setSettingIPTunnelLocal
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIPTunnelLocal
    attrClear = clearSettingIPTunnelLocal
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIPTunnel.local"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIPTunnel.html#g:attr:local"
        })
#endif

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

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

-- | Set the value of the “@mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingIPTunnel [ #mode 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelMode :: (MonadIO m, IsSettingIPTunnel o) => o -> Word32 -> m ()
setSettingIPTunnelMode :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Word32 -> m ()
setSettingIPTunnelMode 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
"mode" Word32
val

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

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

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

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

-- | Set the value of the “@mtu@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingIPTunnel [ #mtu 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelMtu :: (MonadIO m, IsSettingIPTunnel o) => o -> Word32 -> m ()
setSettingIPTunnelMtu :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Word32 -> m ()
setSettingIPTunnelMtu 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
"mtu" Word32
val

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

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

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data SettingIPTunnelOutputKeyPropertyInfo
instance AttrInfo SettingIPTunnelOutputKeyPropertyInfo where
    type AttrAllowedOps SettingIPTunnelOutputKeyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingIPTunnelOutputKeyPropertyInfo = IsSettingIPTunnel
    type AttrSetTypeConstraint SettingIPTunnelOutputKeyPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingIPTunnelOutputKeyPropertyInfo = (~) T.Text
    type AttrTransferType SettingIPTunnelOutputKeyPropertyInfo = T.Text
    type AttrGetType SettingIPTunnelOutputKeyPropertyInfo = T.Text
    type AttrLabel SettingIPTunnelOutputKeyPropertyInfo = "output-key"
    type AttrOrigin SettingIPTunnelOutputKeyPropertyInfo = SettingIPTunnel
    attrGet = getSettingIPTunnelOutputKey
    attrSet = setSettingIPTunnelOutputKey
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIPTunnelOutputKey
    attrClear = clearSettingIPTunnelOutputKey
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIPTunnel.outputKey"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIPTunnel.html#g:attr:outputKey"
        })
#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' settingIPTunnel #parent
-- @
getSettingIPTunnelParent :: (MonadIO m, IsSettingIPTunnel o) => o -> m T.Text
getSettingIPTunnelParent :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m Text
getSettingIPTunnelParent 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
"getSettingIPTunnelParent" (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' settingIPTunnel [ #parent 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelParent :: (MonadIO m, IsSettingIPTunnel o) => o -> T.Text -> m ()
setSettingIPTunnelParent :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Text -> m ()
setSettingIPTunnelParent 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`.
constructSettingIPTunnelParent :: (IsSettingIPTunnel o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingIPTunnelParent :: forall o (m :: * -> *).
(IsSettingIPTunnel o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingIPTunnelParent 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
-- @
clearSettingIPTunnelParent :: (MonadIO m, IsSettingIPTunnel o) => o -> m ()
clearSettingIPTunnelParent :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m ()
clearSettingIPTunnelParent 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 SettingIPTunnelParentPropertyInfo
instance AttrInfo SettingIPTunnelParentPropertyInfo where
    type AttrAllowedOps SettingIPTunnelParentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingIPTunnelParentPropertyInfo = IsSettingIPTunnel
    type AttrSetTypeConstraint SettingIPTunnelParentPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingIPTunnelParentPropertyInfo = (~) T.Text
    type AttrTransferType SettingIPTunnelParentPropertyInfo = T.Text
    type AttrGetType SettingIPTunnelParentPropertyInfo = T.Text
    type AttrLabel SettingIPTunnelParentPropertyInfo = "parent"
    type AttrOrigin SettingIPTunnelParentPropertyInfo = SettingIPTunnel
    attrGet = getSettingIPTunnelParent
    attrSet = setSettingIPTunnelParent
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIPTunnelParent
    attrClear = clearSettingIPTunnelParent
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIPTunnel.parent"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIPTunnel.html#g:attr:parent"
        })
#endif

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

-- | Get the value of the “@path-mtu-discovery@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingIPTunnel #pathMtuDiscovery
-- @
getSettingIPTunnelPathMtuDiscovery :: (MonadIO m, IsSettingIPTunnel o) => o -> m Bool
getSettingIPTunnelPathMtuDiscovery :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m Bool
getSettingIPTunnelPathMtuDiscovery 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
"path-mtu-discovery"

-- | Set the value of the “@path-mtu-discovery@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingIPTunnel [ #pathMtuDiscovery 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelPathMtuDiscovery :: (MonadIO m, IsSettingIPTunnel o) => o -> Bool -> m ()
setSettingIPTunnelPathMtuDiscovery :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Bool -> m ()
setSettingIPTunnelPathMtuDiscovery 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
"path-mtu-discovery" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data SettingIPTunnelPathMtuDiscoveryPropertyInfo
instance AttrInfo SettingIPTunnelPathMtuDiscoveryPropertyInfo where
    type AttrAllowedOps SettingIPTunnelPathMtuDiscoveryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingIPTunnelPathMtuDiscoveryPropertyInfo = IsSettingIPTunnel
    type AttrSetTypeConstraint SettingIPTunnelPathMtuDiscoveryPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingIPTunnelPathMtuDiscoveryPropertyInfo = (~) Bool
    type AttrTransferType SettingIPTunnelPathMtuDiscoveryPropertyInfo = Bool
    type AttrGetType SettingIPTunnelPathMtuDiscoveryPropertyInfo = Bool
    type AttrLabel SettingIPTunnelPathMtuDiscoveryPropertyInfo = "path-mtu-discovery"
    type AttrOrigin SettingIPTunnelPathMtuDiscoveryPropertyInfo = SettingIPTunnel
    attrGet = getSettingIPTunnelPathMtuDiscovery
    attrSet = setSettingIPTunnelPathMtuDiscovery
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIPTunnelPathMtuDiscovery
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIPTunnel.pathMtuDiscovery"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIPTunnel.html#g:attr:pathMtuDiscovery"
        })
#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' settingIPTunnel #remote
-- @
getSettingIPTunnelRemote :: (MonadIO m, IsSettingIPTunnel o) => o -> m T.Text
getSettingIPTunnelRemote :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m Text
getSettingIPTunnelRemote 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
"getSettingIPTunnelRemote" (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' settingIPTunnel [ #remote 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelRemote :: (MonadIO m, IsSettingIPTunnel o) => o -> T.Text -> m ()
setSettingIPTunnelRemote :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Text -> m ()
setSettingIPTunnelRemote 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`.
constructSettingIPTunnelRemote :: (IsSettingIPTunnel o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingIPTunnelRemote :: forall o (m :: * -> *).
(IsSettingIPTunnel o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingIPTunnelRemote 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
-- @
clearSettingIPTunnelRemote :: (MonadIO m, IsSettingIPTunnel o) => o -> m ()
clearSettingIPTunnelRemote :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m ()
clearSettingIPTunnelRemote 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 SettingIPTunnelRemotePropertyInfo
instance AttrInfo SettingIPTunnelRemotePropertyInfo where
    type AttrAllowedOps SettingIPTunnelRemotePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingIPTunnelRemotePropertyInfo = IsSettingIPTunnel
    type AttrSetTypeConstraint SettingIPTunnelRemotePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingIPTunnelRemotePropertyInfo = (~) T.Text
    type AttrTransferType SettingIPTunnelRemotePropertyInfo = T.Text
    type AttrGetType SettingIPTunnelRemotePropertyInfo = T.Text
    type AttrLabel SettingIPTunnelRemotePropertyInfo = "remote"
    type AttrOrigin SettingIPTunnelRemotePropertyInfo = SettingIPTunnel
    attrGet = getSettingIPTunnelRemote
    attrSet = setSettingIPTunnelRemote
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIPTunnelRemote
    attrClear = clearSettingIPTunnelRemote
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIPTunnel.remote"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIPTunnel.html#g:attr:remote"
        })
#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' settingIPTunnel #tos
-- @
getSettingIPTunnelTos :: (MonadIO m, IsSettingIPTunnel o) => o -> m Word32
getSettingIPTunnelTos :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m Word32
getSettingIPTunnelTos 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' settingIPTunnel [ #tos 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelTos :: (MonadIO m, IsSettingIPTunnel o) => o -> Word32 -> m ()
setSettingIPTunnelTos :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Word32 -> m ()
setSettingIPTunnelTos 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`.
constructSettingIPTunnelTos :: (IsSettingIPTunnel o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingIPTunnelTos :: forall o (m :: * -> *).
(IsSettingIPTunnel o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingIPTunnelTos 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 SettingIPTunnelTosPropertyInfo
instance AttrInfo SettingIPTunnelTosPropertyInfo where
    type AttrAllowedOps SettingIPTunnelTosPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingIPTunnelTosPropertyInfo = IsSettingIPTunnel
    type AttrSetTypeConstraint SettingIPTunnelTosPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingIPTunnelTosPropertyInfo = (~) Word32
    type AttrTransferType SettingIPTunnelTosPropertyInfo = Word32
    type AttrGetType SettingIPTunnelTosPropertyInfo = Word32
    type AttrLabel SettingIPTunnelTosPropertyInfo = "tos"
    type AttrOrigin SettingIPTunnelTosPropertyInfo = SettingIPTunnel
    attrGet = getSettingIPTunnelTos
    attrSet = setSettingIPTunnelTos
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIPTunnelTos
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIPTunnel.tos"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIPTunnel.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' settingIPTunnel #ttl
-- @
getSettingIPTunnelTtl :: (MonadIO m, IsSettingIPTunnel o) => o -> m Word32
getSettingIPTunnelTtl :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> m Word32
getSettingIPTunnelTtl 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' settingIPTunnel [ #ttl 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingIPTunnelTtl :: (MonadIO m, IsSettingIPTunnel o) => o -> Word32 -> m ()
setSettingIPTunnelTtl :: forall (m :: * -> *) o.
(MonadIO m, IsSettingIPTunnel o) =>
o -> Word32 -> m ()
setSettingIPTunnelTtl 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`.
constructSettingIPTunnelTtl :: (IsSettingIPTunnel o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingIPTunnelTtl :: forall o (m :: * -> *).
(IsSettingIPTunnel o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingIPTunnelTtl 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 SettingIPTunnelTtlPropertyInfo
instance AttrInfo SettingIPTunnelTtlPropertyInfo where
    type AttrAllowedOps SettingIPTunnelTtlPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingIPTunnelTtlPropertyInfo = IsSettingIPTunnel
    type AttrSetTypeConstraint SettingIPTunnelTtlPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingIPTunnelTtlPropertyInfo = (~) Word32
    type AttrTransferType SettingIPTunnelTtlPropertyInfo = Word32
    type AttrGetType SettingIPTunnelTtlPropertyInfo = Word32
    type AttrLabel SettingIPTunnelTtlPropertyInfo = "ttl"
    type AttrOrigin SettingIPTunnelTtlPropertyInfo = SettingIPTunnel
    attrGet = getSettingIPTunnelTtl
    attrSet = setSettingIPTunnelTtl
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingIPTunnelTtl
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingIPTunnel.ttl"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingIPTunnel.html#g:attr:ttl"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingIPTunnel
type instance O.AttributeList SettingIPTunnel = SettingIPTunnelAttributeList
type SettingIPTunnelAttributeList = ('[ '("encapsulationLimit", SettingIPTunnelEncapsulationLimitPropertyInfo), '("flags", SettingIPTunnelFlagsPropertyInfo), '("flowLabel", SettingIPTunnelFlowLabelPropertyInfo), '("fwmark", SettingIPTunnelFwmarkPropertyInfo), '("inputKey", SettingIPTunnelInputKeyPropertyInfo), '("local", SettingIPTunnelLocalPropertyInfo), '("mode", SettingIPTunnelModePropertyInfo), '("mtu", SettingIPTunnelMtuPropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("outputKey", SettingIPTunnelOutputKeyPropertyInfo), '("parent", SettingIPTunnelParentPropertyInfo), '("pathMtuDiscovery", SettingIPTunnelPathMtuDiscoveryPropertyInfo), '("remote", SettingIPTunnelRemotePropertyInfo), '("tos", SettingIPTunnelTosPropertyInfo), '("ttl", SettingIPTunnelTtlPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingIPTunnelEncapsulationLimit :: AttrLabelProxy "encapsulationLimit"
settingIPTunnelEncapsulationLimit = AttrLabelProxy

settingIPTunnelFlags :: AttrLabelProxy "flags"
settingIPTunnelFlags = AttrLabelProxy

settingIPTunnelFlowLabel :: AttrLabelProxy "flowLabel"
settingIPTunnelFlowLabel = AttrLabelProxy

settingIPTunnelFwmark :: AttrLabelProxy "fwmark"
settingIPTunnelFwmark = AttrLabelProxy

settingIPTunnelInputKey :: AttrLabelProxy "inputKey"
settingIPTunnelInputKey = AttrLabelProxy

settingIPTunnelLocal :: AttrLabelProxy "local"
settingIPTunnelLocal = AttrLabelProxy

settingIPTunnelMode :: AttrLabelProxy "mode"
settingIPTunnelMode = AttrLabelProxy

settingIPTunnelMtu :: AttrLabelProxy "mtu"
settingIPTunnelMtu = AttrLabelProxy

settingIPTunnelOutputKey :: AttrLabelProxy "outputKey"
settingIPTunnelOutputKey = AttrLabelProxy

settingIPTunnelParent :: AttrLabelProxy "parent"
settingIPTunnelParent = AttrLabelProxy

settingIPTunnelPathMtuDiscovery :: AttrLabelProxy "pathMtuDiscovery"
settingIPTunnelPathMtuDiscovery = AttrLabelProxy

settingIPTunnelRemote :: AttrLabelProxy "remote"
settingIPTunnelRemote = AttrLabelProxy

settingIPTunnelTos :: AttrLabelProxy "tos"
settingIPTunnelTos = AttrLabelProxy

settingIPTunnelTtl :: AttrLabelProxy "ttl"
settingIPTunnelTtl = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "nm_setting_ip_tunnel_new" nm_setting_ip_tunnel_new :: 
    IO (Ptr SettingIPTunnel)

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

#if defined(ENABLE_OVERLOADING)
#endif

-- method SettingIPTunnel::get_encapsulation_limit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingIPTunnel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingIPTunnel"
--                 , 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_ip_tunnel_get_encapsulation_limit" nm_setting_ip_tunnel_get_encapsulation_limit :: 
    Ptr SettingIPTunnel ->                  -- setting : TInterface (Name {namespace = "NM", name = "SettingIPTunnel"})
    IO Word32

-- | Returns the [SettingIPTunnel:encapsulationLimit]("GI.NM.Objects.SettingIPTunnel#g:attr:encapsulationLimit") property of the setting.
-- 
-- /Since: 1.42/
settingIPTunnelGetEncapsulationLimit ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m Word32
    -- ^ __Returns:__ the encapsulation limit value
settingIPTunnelGetEncapsulationLimit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Word32
settingIPTunnelGetEncapsulationLimit 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingIPTunnel -> IO Word32
nm_setting_ip_tunnel_get_encapsulation_limit Ptr SettingIPTunnel
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 SettingIPTunnelGetEncapsulationLimitMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetEncapsulationLimitMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetEncapsulationLimit

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


#endif

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

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

-- | Returns the [SettingIPTunnel:flags]("GI.NM.Objects.SettingIPTunnel#g:attr:flags") property of the setting.
-- 
-- /Since: 1.12/
settingIPTunnelGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m [NM.Flags.IPTunnelFlags]
    -- ^ __Returns:__ the tunnel flags
settingIPTunnelGetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m [IPTunnelFlags]
settingIPTunnelGetFlags a
setting = IO [IPTunnelFlags] -> m [IPTunnelFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [IPTunnelFlags] -> m [IPTunnelFlags])
-> IO [IPTunnelFlags] -> m [IPTunnelFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CUInt
result <- Ptr SettingIPTunnel -> IO CUInt
nm_setting_ip_tunnel_get_flags Ptr SettingIPTunnel
setting'
    let result' :: [IPTunnelFlags]
result' = CUInt -> [IPTunnelFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    [IPTunnelFlags] -> IO [IPTunnelFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [IPTunnelFlags]
result'

#if defined(ENABLE_OVERLOADING)
data SettingIPTunnelGetFlagsMethodInfo
instance (signature ~ (m [NM.Flags.IPTunnelFlags]), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetFlagsMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetFlags

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


#endif

-- method SettingIPTunnel::get_flow_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingIPTunnel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingIPTunnel"
--                 , 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_ip_tunnel_get_flow_label" nm_setting_ip_tunnel_get_flow_label :: 
    Ptr SettingIPTunnel ->                  -- setting : TInterface (Name {namespace = "NM", name = "SettingIPTunnel"})
    IO Word32

-- | Returns the [SettingIPTunnel:flowLabel]("GI.NM.Objects.SettingIPTunnel#g:attr:flowLabel") property of the setting.
-- 
-- /Since: 1.42/
settingIPTunnelGetFlowLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m Word32
    -- ^ __Returns:__ the flow label value
settingIPTunnelGetFlowLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Word32
settingIPTunnelGetFlowLabel 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingIPTunnel -> IO Word32
nm_setting_ip_tunnel_get_flow_label Ptr SettingIPTunnel
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 SettingIPTunnelGetFlowLabelMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetFlowLabelMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetFlowLabel

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


#endif

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

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

-- | Returns the [SettingIPTunnel:fwmark]("GI.NM.Objects.SettingIPTunnel#g:attr:fwmark") property of the setting.
-- 
-- /Since: 1.42/
settingIPTunnelGetFwmark ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m Word32
    -- ^ __Returns:__ the fwmark value
settingIPTunnelGetFwmark :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Word32
settingIPTunnelGetFwmark 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingIPTunnel -> IO Word32
nm_setting_ip_tunnel_get_fwmark Ptr SettingIPTunnel
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 SettingIPTunnelGetFwmarkMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetFwmarkMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetFwmark

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


#endif

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

-- | Returns the [SettingIPTunnel:inputKey]("GI.NM.Objects.SettingIPTunnel#g:attr:inputKey") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetInputKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m T.Text
    -- ^ __Returns:__ the input key
settingIPTunnelGetInputKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Text
settingIPTunnelGetInputKey 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingIPTunnel -> IO CString
nm_setting_ip_tunnel_get_input_key Ptr SettingIPTunnel
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingIPTunnelGetInputKey" 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 SettingIPTunnelGetInputKeyMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetInputKeyMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetInputKey

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


#endif

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

-- | Returns the [SettingIPTunnel:local]("GI.NM.Objects.SettingIPTunnel#g:attr:local") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetLocal ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m T.Text
    -- ^ __Returns:__ the local endpoint
settingIPTunnelGetLocal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Text
settingIPTunnelGetLocal 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingIPTunnel -> IO CString
nm_setting_ip_tunnel_get_local Ptr SettingIPTunnel
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingIPTunnelGetLocal" 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 SettingIPTunnelGetLocalMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetLocalMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetLocal

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


#endif

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

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

-- | Returns the [SettingIPTunnel:mode]("GI.NM.Objects.SettingIPTunnel#g:attr:mode") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m NM.Enums.IPTunnelMode
    -- ^ __Returns:__ the tunnel mode
settingIPTunnelGetMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m IPTunnelMode
settingIPTunnelGetMode a
setting = IO IPTunnelMode -> m IPTunnelMode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IPTunnelMode -> m IPTunnelMode)
-> IO IPTunnelMode -> m IPTunnelMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CUInt
result <- Ptr SettingIPTunnel -> IO CUInt
nm_setting_ip_tunnel_get_mode Ptr SettingIPTunnel
setting'
    let result' :: IPTunnelMode
result' = (Int -> IPTunnelMode
forall a. Enum a => Int -> a
toEnum (Int -> IPTunnelMode) -> (CUInt -> Int) -> CUInt -> IPTunnelMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    IPTunnelMode -> IO IPTunnelMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IPTunnelMode
result'

#if defined(ENABLE_OVERLOADING)
data SettingIPTunnelGetModeMethodInfo
instance (signature ~ (m NM.Enums.IPTunnelMode), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetModeMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetMode

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


#endif

-- method SettingIPTunnel::get_mtu
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingIPTunnel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingIPTunnel"
--                 , 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_ip_tunnel_get_mtu" nm_setting_ip_tunnel_get_mtu :: 
    Ptr SettingIPTunnel ->                  -- setting : TInterface (Name {namespace = "NM", name = "SettingIPTunnel"})
    IO Word32

-- | Returns the [SettingIPTunnel:mtu]("GI.NM.Objects.SettingIPTunnel#g:attr:mtu") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetMtu ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m Word32
    -- ^ __Returns:__ the MTU
settingIPTunnelGetMtu :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Word32
settingIPTunnelGetMtu 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingIPTunnel -> IO Word32
nm_setting_ip_tunnel_get_mtu Ptr SettingIPTunnel
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 SettingIPTunnelGetMtuMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetMtuMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetMtu

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


#endif

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

-- | Returns the [SettingIPTunnel:outputKey]("GI.NM.Objects.SettingIPTunnel#g:attr:outputKey") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetOutputKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m T.Text
    -- ^ __Returns:__ the output key
settingIPTunnelGetOutputKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Text
settingIPTunnelGetOutputKey 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingIPTunnel -> IO CString
nm_setting_ip_tunnel_get_output_key Ptr SettingIPTunnel
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingIPTunnelGetOutputKey" 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 SettingIPTunnelGetOutputKeyMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetOutputKeyMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetOutputKey

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


#endif

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

-- | Returns the [SettingIPTunnel:parent]("GI.NM.Objects.SettingIPTunnel#g:attr:parent") property of the setting
-- 
-- /Since: 1.2/
settingIPTunnelGetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m T.Text
    -- ^ __Returns:__ the parent device
settingIPTunnelGetParent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Text
settingIPTunnelGetParent 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingIPTunnel -> IO CString
nm_setting_ip_tunnel_get_parent Ptr SettingIPTunnel
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingIPTunnelGetParent" 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 SettingIPTunnelGetParentMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetParentMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetParent

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


#endif

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

-- | Returns the [SettingIPTunnel:pathMtuDiscovery]("GI.NM.Objects.SettingIPTunnel#g:attr:pathMtuDiscovery") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetPathMtuDiscovery ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m Bool
    -- ^ __Returns:__ whether path MTU discovery is enabled
settingIPTunnelGetPathMtuDiscovery :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Bool
settingIPTunnelGetPathMtuDiscovery 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingIPTunnel -> IO CInt
nm_setting_ip_tunnel_get_path_mtu_discovery Ptr SettingIPTunnel
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 SettingIPTunnelGetPathMtuDiscoveryMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetPathMtuDiscoveryMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetPathMtuDiscovery

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


#endif

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

-- | Returns the [SettingIPTunnel:remote]("GI.NM.Objects.SettingIPTunnel#g:attr:remote") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetRemote ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m T.Text
    -- ^ __Returns:__ the remote endpoint
settingIPTunnelGetRemote :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Text
settingIPTunnelGetRemote 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingIPTunnel -> IO CString
nm_setting_ip_tunnel_get_remote Ptr SettingIPTunnel
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingIPTunnelGetRemote" 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 SettingIPTunnelGetRemoteMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetRemoteMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetRemote

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


#endif

-- method SettingIPTunnel::get_tos
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingIPTunnel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingIPTunnel"
--                 , 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_ip_tunnel_get_tos" nm_setting_ip_tunnel_get_tos :: 
    Ptr SettingIPTunnel ->                  -- setting : TInterface (Name {namespace = "NM", name = "SettingIPTunnel"})
    IO Word32

-- | Returns the [SettingIPTunnel:tos]("GI.NM.Objects.SettingIPTunnel#g:attr:tos") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetTos ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m Word32
    -- ^ __Returns:__ the TOS value
settingIPTunnelGetTos :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Word32
settingIPTunnelGetTos 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingIPTunnel -> IO Word32
nm_setting_ip_tunnel_get_tos Ptr SettingIPTunnel
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 SettingIPTunnelGetTosMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetTosMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetTos

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


#endif

-- method SettingIPTunnel::get_ttl
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingIPTunnel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingIPTunnel"
--                 , 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_ip_tunnel_get_ttl" nm_setting_ip_tunnel_get_ttl :: 
    Ptr SettingIPTunnel ->                  -- setting : TInterface (Name {namespace = "NM", name = "SettingIPTunnel"})
    IO Word32

-- | Returns the [SettingIPTunnel:ttl]("GI.NM.Objects.SettingIPTunnel#g:attr:ttl") property of the setting.
-- 
-- /Since: 1.2/
settingIPTunnelGetTtl ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingIPTunnel.SettingIPTunnel'
    -> m Word32
    -- ^ __Returns:__ the Time-to-live value
settingIPTunnelGetTtl :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingIPTunnel a) =>
a -> m Word32
settingIPTunnelGetTtl 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 SettingIPTunnel
setting' <- a -> IO (Ptr SettingIPTunnel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingIPTunnel -> IO Word32
nm_setting_ip_tunnel_get_ttl Ptr SettingIPTunnel
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 SettingIPTunnelGetTtlMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingIPTunnel a) => O.OverloadedMethod SettingIPTunnelGetTtlMethodInfo a signature where
    overloadedMethod = settingIPTunnelGetTtl

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


#endif