{-# LANGUAGE TypeApplications #-}


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

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

module GI.NM.Objects.SettingTun
    ( 

-- * Exported types
    SettingTun(..)                          ,
    IsSettingTun                            ,
    toSettingTun                            ,


 -- * 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"), [getGroup]("GI.NM.Objects.SettingTun#g:method:getGroup"), [getMode]("GI.NM.Objects.SettingTun#g:method:getMode"), [getMultiQueue]("GI.NM.Objects.SettingTun#g:method:getMultiQueue"), [getName]("GI.NM.Objects.Setting#g:method:getName"), [getOwner]("GI.NM.Objects.SettingTun#g:method:getOwner"), [getPi]("GI.NM.Objects.SettingTun#g:method:getPi"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSecretFlags]("GI.NM.Objects.Setting#g:method:getSecretFlags"), [getVnetHdr]("GI.NM.Objects.SettingTun#g:method:getVnetHdr").
-- 
-- ==== 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)
    ResolveSettingTunMethod                 ,
#endif

-- ** getGroup #method:getGroup#

#if defined(ENABLE_OVERLOADING)
    SettingTunGetGroupMethodInfo            ,
#endif
    settingTunGetGroup                      ,


-- ** getMode #method:getMode#

#if defined(ENABLE_OVERLOADING)
    SettingTunGetModeMethodInfo             ,
#endif
    settingTunGetMode                       ,


-- ** getMultiQueue #method:getMultiQueue#

#if defined(ENABLE_OVERLOADING)
    SettingTunGetMultiQueueMethodInfo       ,
#endif
    settingTunGetMultiQueue                 ,


-- ** getOwner #method:getOwner#

#if defined(ENABLE_OVERLOADING)
    SettingTunGetOwnerMethodInfo            ,
#endif
    settingTunGetOwner                      ,


-- ** getPi #method:getPi#

#if defined(ENABLE_OVERLOADING)
    SettingTunGetPiMethodInfo               ,
#endif
    settingTunGetPi                         ,


-- ** getVnetHdr #method:getVnetHdr#

#if defined(ENABLE_OVERLOADING)
    SettingTunGetVnetHdrMethodInfo          ,
#endif
    settingTunGetVnetHdr                    ,


-- ** new #method:new#

    settingTunNew                           ,




 -- * Properties


-- ** group #attr:group#
-- | The group ID which will own the device. If set to 'P.Nothing' everyone
-- will be able to use the device.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingTunGroupPropertyInfo             ,
#endif
    clearSettingTunGroup                    ,
    constructSettingTunGroup                ,
    getSettingTunGroup                      ,
    setSettingTunGroup                      ,
#if defined(ENABLE_OVERLOADING)
    settingTunGroup                         ,
#endif


-- ** mode #attr:mode#
-- | The operating mode of the virtual device. Allowed values are
-- 'GI.NM.Enums.SettingTunModeTun' to create a layer 3 device and
-- 'GI.NM.Enums.SettingTunModeTap' to create an Ethernet-like layer 2
-- one.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingTunModePropertyInfo              ,
#endif
    constructSettingTunMode                 ,
    getSettingTunMode                       ,
    setSettingTunMode                       ,
#if defined(ENABLE_OVERLOADING)
    settingTunMode                          ,
#endif


-- ** multiQueue #attr:multiQueue#
-- | If the property is set to 'P.True', the interface will support
-- multiple file descriptors (queues) to parallelize packet
-- sending or receiving. Otherwise, the interface will only
-- support a single queue.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingTunMultiQueuePropertyInfo        ,
#endif
    constructSettingTunMultiQueue           ,
    getSettingTunMultiQueue                 ,
    setSettingTunMultiQueue                 ,
#if defined(ENABLE_OVERLOADING)
    settingTunMultiQueue                    ,
#endif


-- ** owner #attr:owner#
-- | The user ID which will own the device. If set to 'P.Nothing' everyone
-- will be able to use the device.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingTunOwnerPropertyInfo             ,
#endif
    clearSettingTunOwner                    ,
    constructSettingTunOwner                ,
    getSettingTunOwner                      ,
    setSettingTunOwner                      ,
#if defined(ENABLE_OVERLOADING)
    settingTunOwner                         ,
#endif


-- ** pi #attr:pi#
-- | If 'P.True' the interface will prepend a 4 byte header describing the
-- physical interface to the packets.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingTunPiPropertyInfo                ,
#endif
    constructSettingTunPi                   ,
    getSettingTunPi                         ,
    setSettingTunPi                         ,
#if defined(ENABLE_OVERLOADING)
    settingTunPi                            ,
#endif


-- ** vnetHdr #attr:vnetHdr#
-- | If 'P.True' the IFF_VNET_HDR the tunnel packets will include a virtio
-- network header.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingTunVnetHdrPropertyInfo           ,
#endif
    constructSettingTunVnetHdr              ,
    getSettingTunVnetHdr                    ,
    setSettingTunVnetHdr                    ,
#if defined(ENABLE_OVERLOADING)
    settingTunVnetHdr                       ,
#endif




    ) where

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

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

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

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

#endif

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

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

foreign import ccall "nm_setting_tun_get_type"
    c_nm_setting_tun_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingTun where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_tun_get_type

instance B.Types.GObject SettingTun

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

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

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

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

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

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

#endif

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

#endif

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data SettingTunGroupPropertyInfo
instance AttrInfo SettingTunGroupPropertyInfo where
    type AttrAllowedOps SettingTunGroupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingTunGroupPropertyInfo = IsSettingTun
    type AttrSetTypeConstraint SettingTunGroupPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingTunGroupPropertyInfo = (~) T.Text
    type AttrTransferType SettingTunGroupPropertyInfo = T.Text
    type AttrGetType SettingTunGroupPropertyInfo = T.Text
    type AttrLabel SettingTunGroupPropertyInfo = "group"
    type AttrOrigin SettingTunGroupPropertyInfo = SettingTun
    attrGet = getSettingTunGroup
    attrSet = setSettingTunGroup
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingTunGroup
    attrClear = clearSettingTunGroup
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingTun.group"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingTun.html#g:attr:group"
        })
#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' settingTun #mode
-- @
getSettingTunMode :: (MonadIO m, IsSettingTun o) => o -> m Word32
getSettingTunMode :: forall (m :: * -> *) o.
(MonadIO m, IsSettingTun o) =>
o -> m Word32
getSettingTunMode 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' settingTun [ #mode 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingTunMode :: (MonadIO m, IsSettingTun o) => o -> Word32 -> m ()
setSettingTunMode :: forall (m :: * -> *) o.
(MonadIO m, IsSettingTun o) =>
o -> Word32 -> m ()
setSettingTunMode 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`.
constructSettingTunMode :: (IsSettingTun o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingTunMode :: forall o (m :: * -> *).
(IsSettingTun o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingTunMode 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 SettingTunModePropertyInfo
instance AttrInfo SettingTunModePropertyInfo where
    type AttrAllowedOps SettingTunModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingTunModePropertyInfo = IsSettingTun
    type AttrSetTypeConstraint SettingTunModePropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingTunModePropertyInfo = (~) Word32
    type AttrTransferType SettingTunModePropertyInfo = Word32
    type AttrGetType SettingTunModePropertyInfo = Word32
    type AttrLabel SettingTunModePropertyInfo = "mode"
    type AttrOrigin SettingTunModePropertyInfo = SettingTun
    attrGet = getSettingTunMode
    attrSet = setSettingTunMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingTunMode
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingTun.mode"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingTun.html#g:attr:mode"
        })
#endif

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingTun
type instance O.AttributeList SettingTun = SettingTunAttributeList
type SettingTunAttributeList = ('[ '("group", SettingTunGroupPropertyInfo), '("mode", SettingTunModePropertyInfo), '("multiQueue", SettingTunMultiQueuePropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("owner", SettingTunOwnerPropertyInfo), '("pi", SettingTunPiPropertyInfo), '("vnetHdr", SettingTunVnetHdrPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingTunGroup :: AttrLabelProxy "group"
settingTunGroup = AttrLabelProxy

settingTunMode :: AttrLabelProxy "mode"
settingTunMode = AttrLabelProxy

settingTunMultiQueue :: AttrLabelProxy "multiQueue"
settingTunMultiQueue = AttrLabelProxy

settingTunOwner :: AttrLabelProxy "owner"
settingTunOwner = AttrLabelProxy

settingTunPi :: AttrLabelProxy "pi"
settingTunPi = AttrLabelProxy

settingTunVnetHdr :: AttrLabelProxy "vnetHdr"
settingTunVnetHdr = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "nm_setting_tun_new" nm_setting_tun_new :: 
    IO (Ptr SettingTun)

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

#if defined(ENABLE_OVERLOADING)
#endif

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

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

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


#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingTunGetMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingTun a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingTun.SettingTun'
    -> m NM.Enums.SettingTunMode
    -- ^ __Returns:__ the [SettingTun:mode]("GI.NM.Objects.SettingTun#g:attr:mode") property of the setting
settingTunGetMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingTun a) =>
a -> m SettingTunMode
settingTunGetMode a
setting = IO SettingTunMode -> m SettingTunMode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingTunMode -> m SettingTunMode)
-> IO SettingTunMode -> m SettingTunMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingTun
setting' <- a -> IO (Ptr SettingTun)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CUInt
result <- Ptr SettingTun -> IO CUInt
nm_setting_tun_get_mode Ptr SettingTun
setting'
    let result' :: SettingTunMode
result' = (Int -> SettingTunMode
forall a. Enum a => Int -> a
toEnum (Int -> SettingTunMode)
-> (CUInt -> Int) -> CUInt -> SettingTunMode
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
    SettingTunMode -> IO SettingTunMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SettingTunMode
result'

#if defined(ENABLE_OVERLOADING)
data SettingTunGetModeMethodInfo
instance (signature ~ (m NM.Enums.SettingTunMode), MonadIO m, IsSettingTun a) => O.OverloadedMethod SettingTunGetModeMethodInfo a signature where
    overloadedMethod = settingTunGetMode

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingTunGetMultiQueue ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingTun a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingTun.SettingTun'
    -> m Bool
    -- ^ __Returns:__ the [SettingTun:multiQueue]("GI.NM.Objects.SettingTun#g:attr:multiQueue") property of the setting
settingTunGetMultiQueue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingTun a) =>
a -> m Bool
settingTunGetMultiQueue 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 SettingTun
setting' <- a -> IO (Ptr SettingTun)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingTun -> IO CInt
nm_setting_tun_get_multi_queue Ptr SettingTun
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 SettingTunGetMultiQueueMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingTun a) => O.OverloadedMethod SettingTunGetMultiQueueMethodInfo a signature where
    overloadedMethod = settingTunGetMultiQueue

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


#endif

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

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

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingTunGetPi ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingTun a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingTun.SettingTun'
    -> m Bool
    -- ^ __Returns:__ the [SettingTun:pi]("GI.NM.Objects.SettingTun#g:attr:pi") property of the setting
settingTunGetPi :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingTun a) =>
a -> m Bool
settingTunGetPi 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 SettingTun
setting' <- a -> IO (Ptr SettingTun)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingTun -> IO CInt
nm_setting_tun_get_pi Ptr SettingTun
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 SettingTunGetPiMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingTun a) => O.OverloadedMethod SettingTunGetPiMethodInfo a signature where
    overloadedMethod = settingTunGetPi

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingTunGetVnetHdr ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingTun a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingTun.SettingTun'
    -> m Bool
    -- ^ __Returns:__ the t'GI.NM.Objects.SettingTun.SettingTun':@/vnet_hdr/@ property of the setting
settingTunGetVnetHdr :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingTun a) =>
a -> m Bool
settingTunGetVnetHdr 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 SettingTun
setting' <- a -> IO (Ptr SettingTun)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingTun -> IO CInt
nm_setting_tun_get_vnet_hdr Ptr SettingTun
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 SettingTunGetVnetHdrMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingTun a) => O.OverloadedMethod SettingTunGetVnetHdrMethodInfo a signature where
    overloadedMethod = settingTunGetVnetHdr

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


#endif