{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- WireGuard Settings
-- 
-- /Since: 1.16/

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

module GI.NM.Objects.SettingWireGuard
    ( 

-- * Exported types
    SettingWireGuard(..)                    ,
    IsSettingWireGuard                      ,
    toSettingWireGuard                      ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [appendPeer]("GI.NM.Objects.SettingWireGuard#g:method:appendPeer"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clearPeers]("GI.NM.Objects.SettingWireGuard#g:method:clearPeers"), [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"), [removePeer]("GI.NM.Objects.SettingWireGuard#g:method:removePeer"), [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"), [getFwmark]("GI.NM.Objects.SettingWireGuard#g:method:getFwmark"), [getIp4AutoDefaultRoute]("GI.NM.Objects.SettingWireGuard#g:method:getIp4AutoDefaultRoute"), [getIp6AutoDefaultRoute]("GI.NM.Objects.SettingWireGuard#g:method:getIp6AutoDefaultRoute"), [getListenPort]("GI.NM.Objects.SettingWireGuard#g:method:getListenPort"), [getMtu]("GI.NM.Objects.SettingWireGuard#g:method:getMtu"), [getName]("GI.NM.Objects.Setting#g:method:getName"), [getPeer]("GI.NM.Objects.SettingWireGuard#g:method:getPeer"), [getPeerByPublicKey]("GI.NM.Objects.SettingWireGuard#g:method:getPeerByPublicKey"), [getPeerRoutes]("GI.NM.Objects.SettingWireGuard#g:method:getPeerRoutes"), [getPeersLen]("GI.NM.Objects.SettingWireGuard#g:method:getPeersLen"), [getPrivateKey]("GI.NM.Objects.SettingWireGuard#g:method:getPrivateKey"), [getPrivateKeyFlags]("GI.NM.Objects.SettingWireGuard#g:method:getPrivateKeyFlags"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSecretFlags]("GI.NM.Objects.Setting#g:method:getSecretFlags").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setPeer]("GI.NM.Objects.SettingWireGuard#g:method:setPeer"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSecretFlags]("GI.NM.Objects.Setting#g:method:setSecretFlags").

#if defined(ENABLE_OVERLOADING)
    ResolveSettingWireGuardMethod           ,
#endif

-- ** appendPeer #method:appendPeer#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardAppendPeerMethodInfo    ,
#endif
    settingWireGuardAppendPeer              ,


-- ** clearPeers #method:clearPeers#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardClearPeersMethodInfo    ,
#endif
    settingWireGuardClearPeers              ,


-- ** getFwmark #method:getFwmark#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetFwmarkMethodInfo     ,
#endif
    settingWireGuardGetFwmark               ,


-- ** getIp4AutoDefaultRoute #method:getIp4AutoDefaultRoute#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetIp4AutoDefaultRouteMethodInfo,
#endif
    settingWireGuardGetIp4AutoDefaultRoute  ,


-- ** getIp6AutoDefaultRoute #method:getIp6AutoDefaultRoute#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetIp6AutoDefaultRouteMethodInfo,
#endif
    settingWireGuardGetIp6AutoDefaultRoute  ,


-- ** getListenPort #method:getListenPort#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetListenPortMethodInfo ,
#endif
    settingWireGuardGetListenPort           ,


-- ** getMtu #method:getMtu#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetMtuMethodInfo        ,
#endif
    settingWireGuardGetMtu                  ,


-- ** getPeer #method:getPeer#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetPeerMethodInfo       ,
#endif
    settingWireGuardGetPeer                 ,


-- ** getPeerByPublicKey #method:getPeerByPublicKey#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetPeerByPublicKeyMethodInfo,
#endif
    settingWireGuardGetPeerByPublicKey      ,


-- ** getPeerRoutes #method:getPeerRoutes#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetPeerRoutesMethodInfo ,
#endif
    settingWireGuardGetPeerRoutes           ,


-- ** getPeersLen #method:getPeersLen#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetPeersLenMethodInfo   ,
#endif
    settingWireGuardGetPeersLen             ,


-- ** getPrivateKey #method:getPrivateKey#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetPrivateKeyMethodInfo ,
#endif
    settingWireGuardGetPrivateKey           ,


-- ** getPrivateKeyFlags #method:getPrivateKeyFlags#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardGetPrivateKeyFlagsMethodInfo,
#endif
    settingWireGuardGetPrivateKeyFlags      ,


-- ** new #method:new#

    settingWireGuardNew                     ,


-- ** removePeer #method:removePeer#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardRemovePeerMethodInfo    ,
#endif
    settingWireGuardRemovePeer              ,


-- ** setPeer #method:setPeer#

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardSetPeerMethodInfo       ,
#endif
    settingWireGuardSetPeer                 ,




 -- * Properties


-- ** fwmark #attr:fwmark#
-- | The use of fwmark is optional and is by default off. Setting it to 0
-- disables it. Otherwise, it is a 32-bit fwmark for outgoing packets.
-- 
-- Note that \"ip4-auto-default-route\" or \"ip6-auto-default-route\" enabled,
-- implies to automatically choose a fwmark.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardFwmarkPropertyInfo      ,
#endif
    constructSettingWireGuardFwmark         ,
    getSettingWireGuardFwmark               ,
    setSettingWireGuardFwmark               ,
#if defined(ENABLE_OVERLOADING)
    settingWireGuardFwmark                  ,
#endif


-- ** ip4AutoDefaultRoute #attr:ip4AutoDefaultRoute#
-- | Whether to enable special handling of the IPv4 default route.
-- If enabled, the IPv4 default route from wireguard.peer-routes
-- will be placed to a dedicated routing-table and two policy routing rules
-- will be added. The fwmark number is also used as routing-table for the default-route,
-- and if fwmark is zero, an unused fwmark\/table is chosen automatically.
-- This corresponds to what wg-quick does with Table=auto and what WireGuard
-- calls \"Improved Rule-based Routing\".
-- 
-- Note that for this automatism to work, you usually don\'t want to set
-- ipv4.gateway, because that will result in a conflicting default route.
-- 
-- Leaving this at the default will enable this option automatically
-- if ipv4.never-default is not set and there are any peers that use
-- a default-route as allowed-ips. Since this automatism only makes
-- sense if you also have a peer with an \/0 allowed-ips, it is usually
-- not necessary to enable this explicitly. However, you can disable
-- it if you want to configure your own routing and rules.
-- 
-- /Since: 1.20/

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardIp4AutoDefaultRoutePropertyInfo,
#endif
    constructSettingWireGuardIp4AutoDefaultRoute,
    getSettingWireGuardIp4AutoDefaultRoute  ,
    setSettingWireGuardIp4AutoDefaultRoute  ,
#if defined(ENABLE_OVERLOADING)
    settingWireGuardIp4AutoDefaultRoute     ,
#endif


-- ** ip6AutoDefaultRoute #attr:ip6AutoDefaultRoute#
-- | Like ip4-auto-default-route, but for the IPv6 default route.
-- 
-- /Since: 1.20/

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardIp6AutoDefaultRoutePropertyInfo,
#endif
    constructSettingWireGuardIp6AutoDefaultRoute,
    getSettingWireGuardIp6AutoDefaultRoute  ,
    setSettingWireGuardIp6AutoDefaultRoute  ,
#if defined(ENABLE_OVERLOADING)
    settingWireGuardIp6AutoDefaultRoute     ,
#endif


-- ** listenPort #attr:listenPort#
-- | The listen-port. If listen-port is not specified, the port will be chosen
-- randomly when the interface comes up.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardListenPortPropertyInfo  ,
#endif
    constructSettingWireGuardListenPort     ,
    getSettingWireGuardListenPort           ,
    setSettingWireGuardListenPort           ,
#if defined(ENABLE_OVERLOADING)
    settingWireGuardListenPort              ,
#endif


-- ** mtu #attr:mtu#
-- | If non-zero, only transmit packets of the specified size or smaller,
-- breaking larger packets up into multiple fragments.
-- 
-- If zero a default MTU is used. Note that contrary to wg-quick\'s MTU
-- setting, this does not take into account the current routes at the
-- time of activation.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardMtuPropertyInfo         ,
#endif
    constructSettingWireGuardMtu            ,
    getSettingWireGuardMtu                  ,
    setSettingWireGuardMtu                  ,
#if defined(ENABLE_OVERLOADING)
    settingWireGuardMtu                     ,
#endif


-- ** peerRoutes #attr:peerRoutes#
-- | Whether to automatically add routes for the AllowedIPs ranges
-- of the peers. If 'P.True' (the default), NetworkManager will automatically
-- add routes in the routing tables according to ipv4.route-table and
-- ipv6.route-table. Usually you want this automatism enabled.
-- If 'P.False', no such routes are added automatically. In this case, the
-- user may want to configure static routes in ipv4.routes and ipv6.routes,
-- respectively.
-- 
-- Note that if the peer\'s AllowedIPs is \"0.0.0.0\/0\" or \"::\/0\" and the profile\'s
-- ipv4.never-default or ipv6.never-default setting is enabled, the peer route for
-- this peer won\'t be added automatically.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardPeerRoutesPropertyInfo  ,
#endif
    constructSettingWireGuardPeerRoutes     ,
    getSettingWireGuardPeerRoutes           ,
    setSettingWireGuardPeerRoutes           ,
#if defined(ENABLE_OVERLOADING)
    settingWireGuardPeerRoutes              ,
#endif


-- ** privateKey #attr:privateKey#
-- | The 256 bit private-key in base64 encoding.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardPrivateKeyPropertyInfo  ,
#endif
    clearSettingWireGuardPrivateKey         ,
    constructSettingWireGuardPrivateKey     ,
    getSettingWireGuardPrivateKey           ,
    setSettingWireGuardPrivateKey           ,
#if defined(ENABLE_OVERLOADING)
    settingWireGuardPrivateKey              ,
#endif


-- ** privateKeyFlags #attr:privateKeyFlags#
-- | Flags indicating how to handle the t'GI.NM.Objects.SettingWirelessSecurity.SettingWirelessSecurity':@/private-key/@
-- property.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    SettingWireGuardPrivateKeyFlagsPropertyInfo,
#endif
    constructSettingWireGuardPrivateKeyFlags,
    getSettingWireGuardPrivateKeyFlags      ,
    setSettingWireGuardPrivateKeyFlags      ,
#if defined(ENABLE_OVERLOADING)
    settingWireGuardPrivateKeyFlags         ,
#endif




    ) where

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

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

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

#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
import {-# SOURCE #-} qualified GI.NM.Structs.WireGuardPeer as NM.WireGuardPeer

#endif

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

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

foreign import ccall "nm_setting_wireguard_get_type"
    c_nm_setting_wireguard_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingWireGuard where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_wireguard_get_type

instance B.Types.GObject SettingWireGuard

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSettingWireGuardMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSettingWireGuardMethod "appendPeer" o = SettingWireGuardAppendPeerMethodInfo
    ResolveSettingWireGuardMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSettingWireGuardMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSettingWireGuardMethod "clearPeers" o = SettingWireGuardClearPeersMethodInfo
    ResolveSettingWireGuardMethod "compare" o = NM.Setting.SettingCompareMethodInfo
    ResolveSettingWireGuardMethod "diff" o = NM.Setting.SettingDiffMethodInfo
    ResolveSettingWireGuardMethod "duplicate" o = NM.Setting.SettingDuplicateMethodInfo
    ResolveSettingWireGuardMethod "enumerateValues" o = NM.Setting.SettingEnumerateValuesMethodInfo
    ResolveSettingWireGuardMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSettingWireGuardMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSettingWireGuardMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSettingWireGuardMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSettingWireGuardMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSettingWireGuardMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSettingWireGuardMethod "optionClearByName" o = NM.Setting.SettingOptionClearByNameMethodInfo
    ResolveSettingWireGuardMethod "optionGet" o = NM.Setting.SettingOptionGetMethodInfo
    ResolveSettingWireGuardMethod "optionGetAllNames" o = NM.Setting.SettingOptionGetAllNamesMethodInfo
    ResolveSettingWireGuardMethod "optionGetBoolean" o = NM.Setting.SettingOptionGetBooleanMethodInfo
    ResolveSettingWireGuardMethod "optionGetUint32" o = NM.Setting.SettingOptionGetUint32MethodInfo
    ResolveSettingWireGuardMethod "optionSet" o = NM.Setting.SettingOptionSetMethodInfo
    ResolveSettingWireGuardMethod "optionSetBoolean" o = NM.Setting.SettingOptionSetBooleanMethodInfo
    ResolveSettingWireGuardMethod "optionSetUint32" o = NM.Setting.SettingOptionSetUint32MethodInfo
    ResolveSettingWireGuardMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSettingWireGuardMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSettingWireGuardMethod "removePeer" o = SettingWireGuardRemovePeerMethodInfo
    ResolveSettingWireGuardMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSettingWireGuardMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSettingWireGuardMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSettingWireGuardMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSettingWireGuardMethod "toString" o = NM.Setting.SettingToStringMethodInfo
    ResolveSettingWireGuardMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSettingWireGuardMethod "verify" o = NM.Setting.SettingVerifyMethodInfo
    ResolveSettingWireGuardMethod "verifySecrets" o = NM.Setting.SettingVerifySecretsMethodInfo
    ResolveSettingWireGuardMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSettingWireGuardMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSettingWireGuardMethod "getDbusPropertyType" o = NM.Setting.SettingGetDbusPropertyTypeMethodInfo
    ResolveSettingWireGuardMethod "getFwmark" o = SettingWireGuardGetFwmarkMethodInfo
    ResolveSettingWireGuardMethod "getIp4AutoDefaultRoute" o = SettingWireGuardGetIp4AutoDefaultRouteMethodInfo
    ResolveSettingWireGuardMethod "getIp6AutoDefaultRoute" o = SettingWireGuardGetIp6AutoDefaultRouteMethodInfo
    ResolveSettingWireGuardMethod "getListenPort" o = SettingWireGuardGetListenPortMethodInfo
    ResolveSettingWireGuardMethod "getMtu" o = SettingWireGuardGetMtuMethodInfo
    ResolveSettingWireGuardMethod "getName" o = NM.Setting.SettingGetNameMethodInfo
    ResolveSettingWireGuardMethod "getPeer" o = SettingWireGuardGetPeerMethodInfo
    ResolveSettingWireGuardMethod "getPeerByPublicKey" o = SettingWireGuardGetPeerByPublicKeyMethodInfo
    ResolveSettingWireGuardMethod "getPeerRoutes" o = SettingWireGuardGetPeerRoutesMethodInfo
    ResolveSettingWireGuardMethod "getPeersLen" o = SettingWireGuardGetPeersLenMethodInfo
    ResolveSettingWireGuardMethod "getPrivateKey" o = SettingWireGuardGetPrivateKeyMethodInfo
    ResolveSettingWireGuardMethod "getPrivateKeyFlags" o = SettingWireGuardGetPrivateKeyFlagsMethodInfo
    ResolveSettingWireGuardMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingWireGuardMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingWireGuardMethod "getSecretFlags" o = NM.Setting.SettingGetSecretFlagsMethodInfo
    ResolveSettingWireGuardMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingWireGuardMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingWireGuardMethod "setPeer" o = SettingWireGuardSetPeerMethodInfo
    ResolveSettingWireGuardMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingWireGuardMethod "setSecretFlags" o = NM.Setting.SettingSetSecretFlagsMethodInfo
    ResolveSettingWireGuardMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#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' settingWireGuard #fwmark
-- @
getSettingWireGuardFwmark :: (MonadIO m, IsSettingWireGuard o) => o -> m Word32
getSettingWireGuardFwmark :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> m Word32
getSettingWireGuardFwmark 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' settingWireGuard [ #fwmark 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingWireGuardFwmark :: (MonadIO m, IsSettingWireGuard o) => o -> Word32 -> m ()
setSettingWireGuardFwmark :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> Word32 -> m ()
setSettingWireGuardFwmark 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`.
constructSettingWireGuardFwmark :: (IsSettingWireGuard o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingWireGuardFwmark :: forall o (m :: * -> *).
(IsSettingWireGuard o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingWireGuardFwmark 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 SettingWireGuardFwmarkPropertyInfo
instance AttrInfo SettingWireGuardFwmarkPropertyInfo where
    type AttrAllowedOps SettingWireGuardFwmarkPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingWireGuardFwmarkPropertyInfo = IsSettingWireGuard
    type AttrSetTypeConstraint SettingWireGuardFwmarkPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingWireGuardFwmarkPropertyInfo = (~) Word32
    type AttrTransferType SettingWireGuardFwmarkPropertyInfo = Word32
    type AttrGetType SettingWireGuardFwmarkPropertyInfo = Word32
    type AttrLabel SettingWireGuardFwmarkPropertyInfo = "fwmark"
    type AttrOrigin SettingWireGuardFwmarkPropertyInfo = SettingWireGuard
    attrGet = getSettingWireGuardFwmark
    attrSet = setSettingWireGuardFwmark
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingWireGuardFwmark
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingWireGuard.fwmark"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingWireGuard.html#g:attr:fwmark"
        })
#endif

-- VVV Prop "ip4-auto-default-route"
   -- Type: TInterface (Name {namespace = "NM", name = "Ternary"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@ip4-auto-default-route@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingWireGuard #ip4AutoDefaultRoute
-- @
getSettingWireGuardIp4AutoDefaultRoute :: (MonadIO m, IsSettingWireGuard o) => o -> m NM.Enums.Ternary
getSettingWireGuardIp4AutoDefaultRoute :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> m Ternary
getSettingWireGuardIp4AutoDefaultRoute o
obj = IO Ternary -> m Ternary
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Ternary -> m Ternary) -> IO Ternary -> m Ternary
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Ternary
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"ip4-auto-default-route"

-- | Set the value of the “@ip4-auto-default-route@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingWireGuard [ #ip4AutoDefaultRoute 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingWireGuardIp4AutoDefaultRoute :: (MonadIO m, IsSettingWireGuard o) => o -> NM.Enums.Ternary -> m ()
setSettingWireGuardIp4AutoDefaultRoute :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> Ternary -> m ()
setSettingWireGuardIp4AutoDefaultRoute o
obj Ternary
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 -> Ternary -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"ip4-auto-default-route" Ternary
val

-- | Construct a t'GValueConstruct' with valid value for the “@ip4-auto-default-route@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingWireGuardIp4AutoDefaultRoute :: (IsSettingWireGuard o, MIO.MonadIO m) => NM.Enums.Ternary -> m (GValueConstruct o)
constructSettingWireGuardIp4AutoDefaultRoute :: forall o (m :: * -> *).
(IsSettingWireGuard o, MonadIO m) =>
Ternary -> m (GValueConstruct o)
constructSettingWireGuardIp4AutoDefaultRoute Ternary
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 -> Ternary -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"ip4-auto-default-route" Ternary
val

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardIp4AutoDefaultRoutePropertyInfo
instance AttrInfo SettingWireGuardIp4AutoDefaultRoutePropertyInfo where
    type AttrAllowedOps SettingWireGuardIp4AutoDefaultRoutePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingWireGuardIp4AutoDefaultRoutePropertyInfo = IsSettingWireGuard
    type AttrSetTypeConstraint SettingWireGuardIp4AutoDefaultRoutePropertyInfo = (~) NM.Enums.Ternary
    type AttrTransferTypeConstraint SettingWireGuardIp4AutoDefaultRoutePropertyInfo = (~) NM.Enums.Ternary
    type AttrTransferType SettingWireGuardIp4AutoDefaultRoutePropertyInfo = NM.Enums.Ternary
    type AttrGetType SettingWireGuardIp4AutoDefaultRoutePropertyInfo = NM.Enums.Ternary
    type AttrLabel SettingWireGuardIp4AutoDefaultRoutePropertyInfo = "ip4-auto-default-route"
    type AttrOrigin SettingWireGuardIp4AutoDefaultRoutePropertyInfo = SettingWireGuard
    attrGet = getSettingWireGuardIp4AutoDefaultRoute
    attrSet = setSettingWireGuardIp4AutoDefaultRoute
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingWireGuardIp4AutoDefaultRoute
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingWireGuard.ip4AutoDefaultRoute"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingWireGuard.html#g:attr:ip4AutoDefaultRoute"
        })
#endif

-- VVV Prop "ip6-auto-default-route"
   -- Type: TInterface (Name {namespace = "NM", name = "Ternary"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@ip6-auto-default-route@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingWireGuard #ip6AutoDefaultRoute
-- @
getSettingWireGuardIp6AutoDefaultRoute :: (MonadIO m, IsSettingWireGuard o) => o -> m NM.Enums.Ternary
getSettingWireGuardIp6AutoDefaultRoute :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> m Ternary
getSettingWireGuardIp6AutoDefaultRoute o
obj = IO Ternary -> m Ternary
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Ternary -> m Ternary) -> IO Ternary -> m Ternary
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Ternary
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"ip6-auto-default-route"

-- | Set the value of the “@ip6-auto-default-route@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingWireGuard [ #ip6AutoDefaultRoute 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingWireGuardIp6AutoDefaultRoute :: (MonadIO m, IsSettingWireGuard o) => o -> NM.Enums.Ternary -> m ()
setSettingWireGuardIp6AutoDefaultRoute :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> Ternary -> m ()
setSettingWireGuardIp6AutoDefaultRoute o
obj Ternary
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 -> Ternary -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"ip6-auto-default-route" Ternary
val

-- | Construct a t'GValueConstruct' with valid value for the “@ip6-auto-default-route@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingWireGuardIp6AutoDefaultRoute :: (IsSettingWireGuard o, MIO.MonadIO m) => NM.Enums.Ternary -> m (GValueConstruct o)
constructSettingWireGuardIp6AutoDefaultRoute :: forall o (m :: * -> *).
(IsSettingWireGuard o, MonadIO m) =>
Ternary -> m (GValueConstruct o)
constructSettingWireGuardIp6AutoDefaultRoute Ternary
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 -> Ternary -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"ip6-auto-default-route" Ternary
val

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardIp6AutoDefaultRoutePropertyInfo
instance AttrInfo SettingWireGuardIp6AutoDefaultRoutePropertyInfo where
    type AttrAllowedOps SettingWireGuardIp6AutoDefaultRoutePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingWireGuardIp6AutoDefaultRoutePropertyInfo = IsSettingWireGuard
    type AttrSetTypeConstraint SettingWireGuardIp6AutoDefaultRoutePropertyInfo = (~) NM.Enums.Ternary
    type AttrTransferTypeConstraint SettingWireGuardIp6AutoDefaultRoutePropertyInfo = (~) NM.Enums.Ternary
    type AttrTransferType SettingWireGuardIp6AutoDefaultRoutePropertyInfo = NM.Enums.Ternary
    type AttrGetType SettingWireGuardIp6AutoDefaultRoutePropertyInfo = NM.Enums.Ternary
    type AttrLabel SettingWireGuardIp6AutoDefaultRoutePropertyInfo = "ip6-auto-default-route"
    type AttrOrigin SettingWireGuardIp6AutoDefaultRoutePropertyInfo = SettingWireGuard
    attrGet = getSettingWireGuardIp6AutoDefaultRoute
    attrSet = setSettingWireGuardIp6AutoDefaultRoute
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingWireGuardIp6AutoDefaultRoute
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingWireGuard.ip6AutoDefaultRoute"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingWireGuard.html#g:attr:ip6AutoDefaultRoute"
        })
#endif

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

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

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

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

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

-- VVV Prop "mtu"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,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' settingWireGuard #mtu
-- @
getSettingWireGuardMtu :: (MonadIO m, IsSettingWireGuard o) => o -> m Word32
getSettingWireGuardMtu :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> m Word32
getSettingWireGuardMtu 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' settingWireGuard [ #mtu 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingWireGuardMtu :: (MonadIO m, IsSettingWireGuard o) => o -> Word32 -> m ()
setSettingWireGuardMtu :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> Word32 -> m ()
setSettingWireGuardMtu 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`.
constructSettingWireGuardMtu :: (IsSettingWireGuard o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingWireGuardMtu :: forall o (m :: * -> *).
(IsSettingWireGuard o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingWireGuardMtu 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 SettingWireGuardMtuPropertyInfo
instance AttrInfo SettingWireGuardMtuPropertyInfo where
    type AttrAllowedOps SettingWireGuardMtuPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingWireGuardMtuPropertyInfo = IsSettingWireGuard
    type AttrSetTypeConstraint SettingWireGuardMtuPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingWireGuardMtuPropertyInfo = (~) Word32
    type AttrTransferType SettingWireGuardMtuPropertyInfo = Word32
    type AttrGetType SettingWireGuardMtuPropertyInfo = Word32
    type AttrLabel SettingWireGuardMtuPropertyInfo = "mtu"
    type AttrOrigin SettingWireGuardMtuPropertyInfo = SettingWireGuard
    attrGet = getSettingWireGuardMtu
    attrSet = setSettingWireGuardMtu
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingWireGuardMtu
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingWireGuard.mtu"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingWireGuard.html#g:attr:mtu"
        })
#endif

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

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

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

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

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

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

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

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

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

-- | Set the value of the “@private-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' #privateKey
-- @
clearSettingWireGuardPrivateKey :: (MonadIO m, IsSettingWireGuard o) => o -> m ()
clearSettingWireGuardPrivateKey :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> m ()
clearSettingWireGuardPrivateKey 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
"private-key" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardPrivateKeyPropertyInfo
instance AttrInfo SettingWireGuardPrivateKeyPropertyInfo where
    type AttrAllowedOps SettingWireGuardPrivateKeyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingWireGuardPrivateKeyPropertyInfo = IsSettingWireGuard
    type AttrSetTypeConstraint SettingWireGuardPrivateKeyPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingWireGuardPrivateKeyPropertyInfo = (~) T.Text
    type AttrTransferType SettingWireGuardPrivateKeyPropertyInfo = T.Text
    type AttrGetType SettingWireGuardPrivateKeyPropertyInfo = T.Text
    type AttrLabel SettingWireGuardPrivateKeyPropertyInfo = "private-key"
    type AttrOrigin SettingWireGuardPrivateKeyPropertyInfo = SettingWireGuard
    attrGet = getSettingWireGuardPrivateKey
    attrSet = setSettingWireGuardPrivateKey
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingWireGuardPrivateKey
    attrClear = clearSettingWireGuardPrivateKey
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingWireGuard.privateKey"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingWireGuard.html#g:attr:privateKey"
        })
#endif

-- VVV Prop "private-key-flags"
   -- Type: TInterface (Name {namespace = "NM", name = "SettingSecretFlags"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@private-key-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingWireGuard #privateKeyFlags
-- @
getSettingWireGuardPrivateKeyFlags :: (MonadIO m, IsSettingWireGuard o) => o -> m [NM.Flags.SettingSecretFlags]
getSettingWireGuardPrivateKeyFlags :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> m [SettingSecretFlags]
getSettingWireGuardPrivateKeyFlags o
obj = IO [SettingSecretFlags] -> m [SettingSecretFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [SettingSecretFlags] -> m [SettingSecretFlags])
-> IO [SettingSecretFlags] -> m [SettingSecretFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [SettingSecretFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"private-key-flags"

-- | Set the value of the “@private-key-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingWireGuard [ #privateKeyFlags 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingWireGuardPrivateKeyFlags :: (MonadIO m, IsSettingWireGuard o) => o -> [NM.Flags.SettingSecretFlags] -> m ()
setSettingWireGuardPrivateKeyFlags :: forall (m :: * -> *) o.
(MonadIO m, IsSettingWireGuard o) =>
o -> [SettingSecretFlags] -> m ()
setSettingWireGuardPrivateKeyFlags o
obj [SettingSecretFlags]
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 -> [SettingSecretFlags] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"private-key-flags" [SettingSecretFlags]
val

-- | Construct a t'GValueConstruct' with valid value for the “@private-key-flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingWireGuardPrivateKeyFlags :: (IsSettingWireGuard o, MIO.MonadIO m) => [NM.Flags.SettingSecretFlags] -> m (GValueConstruct o)
constructSettingWireGuardPrivateKeyFlags :: forall o (m :: * -> *).
(IsSettingWireGuard o, MonadIO m) =>
[SettingSecretFlags] -> m (GValueConstruct o)
constructSettingWireGuardPrivateKeyFlags [SettingSecretFlags]
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 -> [SettingSecretFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"private-key-flags" [SettingSecretFlags]
val

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardPrivateKeyFlagsPropertyInfo
instance AttrInfo SettingWireGuardPrivateKeyFlagsPropertyInfo where
    type AttrAllowedOps SettingWireGuardPrivateKeyFlagsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingWireGuardPrivateKeyFlagsPropertyInfo = IsSettingWireGuard
    type AttrSetTypeConstraint SettingWireGuardPrivateKeyFlagsPropertyInfo = (~) [NM.Flags.SettingSecretFlags]
    type AttrTransferTypeConstraint SettingWireGuardPrivateKeyFlagsPropertyInfo = (~) [NM.Flags.SettingSecretFlags]
    type AttrTransferType SettingWireGuardPrivateKeyFlagsPropertyInfo = [NM.Flags.SettingSecretFlags]
    type AttrGetType SettingWireGuardPrivateKeyFlagsPropertyInfo = [NM.Flags.SettingSecretFlags]
    type AttrLabel SettingWireGuardPrivateKeyFlagsPropertyInfo = "private-key-flags"
    type AttrOrigin SettingWireGuardPrivateKeyFlagsPropertyInfo = SettingWireGuard
    attrGet = getSettingWireGuardPrivateKeyFlags
    attrSet = setSettingWireGuardPrivateKeyFlags
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingWireGuardPrivateKeyFlags
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingWireGuard.privateKeyFlags"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingWireGuard.html#g:attr:privateKeyFlags"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingWireGuard
type instance O.AttributeList SettingWireGuard = SettingWireGuardAttributeList
type SettingWireGuardAttributeList = ('[ '("fwmark", SettingWireGuardFwmarkPropertyInfo), '("ip4AutoDefaultRoute", SettingWireGuardIp4AutoDefaultRoutePropertyInfo), '("ip6AutoDefaultRoute", SettingWireGuardIp6AutoDefaultRoutePropertyInfo), '("listenPort", SettingWireGuardListenPortPropertyInfo), '("mtu", SettingWireGuardMtuPropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("peerRoutes", SettingWireGuardPeerRoutesPropertyInfo), '("privateKey", SettingWireGuardPrivateKeyPropertyInfo), '("privateKeyFlags", SettingWireGuardPrivateKeyFlagsPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingWireGuardFwmark :: AttrLabelProxy "fwmark"
settingWireGuardFwmark = AttrLabelProxy

settingWireGuardIp4AutoDefaultRoute :: AttrLabelProxy "ip4AutoDefaultRoute"
settingWireGuardIp4AutoDefaultRoute = AttrLabelProxy

settingWireGuardIp6AutoDefaultRoute :: AttrLabelProxy "ip6AutoDefaultRoute"
settingWireGuardIp6AutoDefaultRoute = AttrLabelProxy

settingWireGuardListenPort :: AttrLabelProxy "listenPort"
settingWireGuardListenPort = AttrLabelProxy

settingWireGuardMtu :: AttrLabelProxy "mtu"
settingWireGuardMtu = AttrLabelProxy

settingWireGuardPeerRoutes :: AttrLabelProxy "peerRoutes"
settingWireGuardPeerRoutes = AttrLabelProxy

settingWireGuardPrivateKey :: AttrLabelProxy "privateKey"
settingWireGuardPrivateKey = AttrLabelProxy

settingWireGuardPrivateKeyFlags :: AttrLabelProxy "privateKeyFlags"
settingWireGuardPrivateKeyFlags = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "nm_setting_wireguard_new" nm_setting_wireguard_new :: 
    IO (Ptr SettingWireGuard)

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

#if defined(ENABLE_OVERLOADING)
#endif

-- method SettingWireGuard::append_peer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WireGuardPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #NMWireGuardPeer instance to append.\n  This seals @peer and keeps a reference on the\n  instance."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_wireguard_append_peer" nm_setting_wireguard_append_peer :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    Ptr NM.WireGuardPeer.WireGuardPeer ->   -- peer : TInterface (Name {namespace = "NM", name = "WireGuardPeer"})
    IO ()

-- | If a peer with the same public-key already exists, that
-- one is replaced by /@peer@/. The new /@peer@/ is always appended
-- (or moved to) the end, so in case a peer is replaced, the
-- indexes are shifted and the number of peers stays unchanged.
-- 
-- /Since: 1.16/
settingWireGuardAppendPeer ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> NM.WireGuardPeer.WireGuardPeer
    -- ^ /@peer@/: the t'GI.NM.Structs.WireGuardPeer.WireGuardPeer' instance to append.
    --   This seals /@peer@/ and keeps a reference on the
    --   instance.
    -> m ()
settingWireGuardAppendPeer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> WireGuardPeer -> m ()
settingWireGuardAppendPeer a
self WireGuardPeer
peer = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr WireGuardPeer
peer' <- WireGuardPeer -> IO (Ptr WireGuardPeer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WireGuardPeer
peer
    Ptr SettingWireGuard -> Ptr WireGuardPeer -> IO ()
nm_setting_wireguard_append_peer Ptr SettingWireGuard
self' Ptr WireGuardPeer
peer'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    WireGuardPeer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WireGuardPeer
peer
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardAppendPeerMethodInfo
instance (signature ~ (NM.WireGuardPeer.WireGuardPeer -> m ()), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardAppendPeerMethodInfo a signature where
    overloadedMethod = settingWireGuardAppendPeer

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


#endif

-- method SettingWireGuard::clear_peers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , 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_wireguard_clear_peers" nm_setting_wireguard_clear_peers :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO Word32

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardClearPeers ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> m Word32
    -- ^ __Returns:__ the number of cleared peers.
settingWireGuardClearPeers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Word32
settingWireGuardClearPeers a
self = 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 SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word32
result <- Ptr SettingWireGuard -> IO Word32
nm_setting_wireguard_clear_peers Ptr SettingWireGuard
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardClearPeersMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardClearPeersMethodInfo a signature where
    overloadedMethod = settingWireGuardClearPeers

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


#endif

-- method SettingWireGuard::get_fwmark
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , 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_wireguard_get_fwmark" nm_setting_wireguard_get_fwmark :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO Word32

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetFwmark ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> m Word32
    -- ^ __Returns:__ the set firewall mark.
settingWireGuardGetFwmark :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Word32
settingWireGuardGetFwmark a
self = 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 SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word32
result <- Ptr SettingWireGuard -> IO Word32
nm_setting_wireguard_get_fwmark Ptr SettingWireGuard
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetFwmarkMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetFwmarkMethodInfo a signature where
    overloadedMethod = settingWireGuardGetFwmark

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


#endif

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

foreign import ccall "nm_setting_wireguard_get_ip4_auto_default_route" nm_setting_wireguard_get_ip4_auto_default_route :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.20/
settingWireGuardGetIp4AutoDefaultRoute ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' setting.
    -> m NM.Enums.Ternary
    -- ^ __Returns:__ the \"ip4-auto-default-route\" property of the setting.
settingWireGuardGetIp4AutoDefaultRoute :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Ternary
settingWireGuardGetIp4AutoDefaultRoute a
self = IO Ternary -> m Ternary
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Ternary -> m Ternary) -> IO Ternary -> m Ternary
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr SettingWireGuard -> IO CInt
nm_setting_wireguard_get_ip4_auto_default_route Ptr SettingWireGuard
self'
    let result' :: Ternary
result' = (Int -> Ternary
forall a. Enum a => Int -> a
toEnum (Int -> Ternary) -> (CInt -> Int) -> CInt -> Ternary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ternary -> IO Ternary
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ternary
result'

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetIp4AutoDefaultRouteMethodInfo
instance (signature ~ (m NM.Enums.Ternary), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetIp4AutoDefaultRouteMethodInfo a signature where
    overloadedMethod = settingWireGuardGetIp4AutoDefaultRoute

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


#endif

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

foreign import ccall "nm_setting_wireguard_get_ip6_auto_default_route" nm_setting_wireguard_get_ip6_auto_default_route :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.20/
settingWireGuardGetIp6AutoDefaultRoute ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' setting.
    -> m NM.Enums.Ternary
    -- ^ __Returns:__ the \"ip6-auto-default-route\" property of the setting.
settingWireGuardGetIp6AutoDefaultRoute :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Ternary
settingWireGuardGetIp6AutoDefaultRoute a
self = IO Ternary -> m Ternary
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Ternary -> m Ternary) -> IO Ternary -> m Ternary
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr SettingWireGuard -> IO CInt
nm_setting_wireguard_get_ip6_auto_default_route Ptr SettingWireGuard
self'
    let result' :: Ternary
result' = (Int -> Ternary
forall a. Enum a => Int -> a
toEnum (Int -> Ternary) -> (CInt -> Int) -> CInt -> Ternary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ternary -> IO Ternary
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ternary
result'

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetIp6AutoDefaultRouteMethodInfo
instance (signature ~ (m NM.Enums.Ternary), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetIp6AutoDefaultRouteMethodInfo a signature where
    overloadedMethod = settingWireGuardGetIp6AutoDefaultRoute

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


#endif

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

foreign import ccall "nm_setting_wireguard_get_listen_port" nm_setting_wireguard_get_listen_port :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO Word16

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetListenPort ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> m Word16
    -- ^ __Returns:__ the set UDP listen port.
settingWireGuardGetListenPort :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Word16
settingWireGuardGetListenPort a
self = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word16
result <- Ptr SettingWireGuard -> IO Word16
nm_setting_wireguard_get_listen_port Ptr SettingWireGuard
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
result

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetListenPortMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetListenPortMethodInfo a signature where
    overloadedMethod = settingWireGuardGetListenPort

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


#endif

-- method SettingWireGuard::get_mtu
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , 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_wireguard_get_mtu" nm_setting_wireguard_get_mtu :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO Word32

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetMtu ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> m Word32
    -- ^ __Returns:__ the MTU of the setting.
settingWireGuardGetMtu :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Word32
settingWireGuardGetMtu a
self = 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 SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word32
result <- Ptr SettingWireGuard -> IO Word32
nm_setting_wireguard_get_mtu Ptr SettingWireGuard
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetMtuMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetMtuMethodInfo a signature where
    overloadedMethod = settingWireGuardGetMtu

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


#endif

-- method SettingWireGuard::get_peer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "idx"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index to lookup."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "NM" , name = "WireGuardPeer" })
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_wireguard_get_peer" nm_setting_wireguard_get_peer :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    Word32 ->                               -- idx : TBasicType TUInt
    IO (Ptr NM.WireGuardPeer.WireGuardPeer)

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetPeer ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> Word32
    -- ^ /@idx@/: the index to lookup.
    -> m NM.WireGuardPeer.WireGuardPeer
    -- ^ __Returns:__ the t'GI.NM.Structs.WireGuardPeer.WireGuardPeer' entry at
    --   index /@idx@/. If the index is out of range, 'P.Nothing' is returned.
settingWireGuardGetPeer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> Word32 -> m WireGuardPeer
settingWireGuardGetPeer a
self Word32
idx = IO WireGuardPeer -> m WireGuardPeer
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WireGuardPeer -> m WireGuardPeer)
-> IO WireGuardPeer -> m WireGuardPeer
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr WireGuardPeer
result <- Ptr SettingWireGuard -> Word32 -> IO (Ptr WireGuardPeer)
nm_setting_wireguard_get_peer Ptr SettingWireGuard
self' Word32
idx
    Text -> Ptr WireGuardPeer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingWireGuardGetPeer" Ptr WireGuardPeer
result
    WireGuardPeer
result' <- ((ManagedPtr WireGuardPeer -> WireGuardPeer)
-> Ptr WireGuardPeer -> IO WireGuardPeer
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr WireGuardPeer -> WireGuardPeer
NM.WireGuardPeer.WireGuardPeer) Ptr WireGuardPeer
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    WireGuardPeer -> IO WireGuardPeer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WireGuardPeer
result'

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetPeerMethodInfo
instance (signature ~ (Word32 -> m NM.WireGuardPeer.WireGuardPeer), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetPeerMethodInfo a signature where
    overloadedMethod = settingWireGuardGetPeer

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


#endif

-- method SettingWireGuard::get_peer_by_public_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "public_key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the public key for looking up the\n  peer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_idx"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "optional output argument\n  for the index of the found peer. If no index is found,\n  this is set to the nm_setting_wireguard_get_peers_len()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "NM" , name = "WireGuardPeer" })
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_wireguard_get_peer_by_public_key" nm_setting_wireguard_get_peer_by_public_key :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    CString ->                              -- public_key : TBasicType TUTF8
    Ptr Word32 ->                           -- out_idx : TBasicType TUInt
    IO (Ptr NM.WireGuardPeer.WireGuardPeer)

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetPeerByPublicKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> T.Text
    -- ^ /@publicKey@/: the public key for looking up the
    --   peer.
    -> m ((Maybe NM.WireGuardPeer.WireGuardPeer, Word32))
    -- ^ __Returns:__ the t'GI.NM.Structs.WireGuardPeer.WireGuardPeer' instance with a
    --   matching public key. If no such peer exists, 'P.Nothing' is returned.
settingWireGuardGetPeerByPublicKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> Text -> m (Maybe WireGuardPeer, Word32)
settingWireGuardGetPeerByPublicKey a
self Text
publicKey = IO (Maybe WireGuardPeer, Word32) -> m (Maybe WireGuardPeer, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe WireGuardPeer, Word32)
 -> m (Maybe WireGuardPeer, Word32))
-> IO (Maybe WireGuardPeer, Word32)
-> m (Maybe WireGuardPeer, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
publicKey' <- Text -> IO CString
textToCString Text
publicKey
    Ptr Word32
outIdx <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr WireGuardPeer
result <- Ptr SettingWireGuard
-> CString -> Ptr Word32 -> IO (Ptr WireGuardPeer)
nm_setting_wireguard_get_peer_by_public_key Ptr SettingWireGuard
self' CString
publicKey' Ptr Word32
outIdx
    Maybe WireGuardPeer
maybeResult <- Ptr WireGuardPeer
-> (Ptr WireGuardPeer -> IO WireGuardPeer)
-> IO (Maybe WireGuardPeer)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr WireGuardPeer
result ((Ptr WireGuardPeer -> IO WireGuardPeer)
 -> IO (Maybe WireGuardPeer))
-> (Ptr WireGuardPeer -> IO WireGuardPeer)
-> IO (Maybe WireGuardPeer)
forall a b. (a -> b) -> a -> b
$ \Ptr WireGuardPeer
result' -> do
        WireGuardPeer
result'' <- ((ManagedPtr WireGuardPeer -> WireGuardPeer)
-> Ptr WireGuardPeer -> IO WireGuardPeer
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr WireGuardPeer -> WireGuardPeer
NM.WireGuardPeer.WireGuardPeer) Ptr WireGuardPeer
result'
        WireGuardPeer -> IO WireGuardPeer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WireGuardPeer
result''
    Word32
outIdx' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
outIdx
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
publicKey'
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
outIdx
    (Maybe WireGuardPeer, Word32) -> IO (Maybe WireGuardPeer, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe WireGuardPeer
maybeResult, Word32
outIdx')

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetPeerByPublicKeyMethodInfo
instance (signature ~ (T.Text -> m ((Maybe NM.WireGuardPeer.WireGuardPeer, Word32))), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetPeerByPublicKeyMethodInfo a signature where
    overloadedMethod = settingWireGuardGetPeerByPublicKey

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


#endif

-- method SettingWireGuard::get_peer_routes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , 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_wireguard_get_peer_routes" nm_setting_wireguard_get_peer_routes :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetPeerRoutes ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> m Bool
    -- ^ __Returns:__ whether automatically add peer routes.
settingWireGuardGetPeerRoutes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Bool
settingWireGuardGetPeerRoutes a
self = 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 SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr SettingWireGuard -> IO CInt
nm_setting_wireguard_get_peer_routes Ptr SettingWireGuard
self'
    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
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetPeerRoutesMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetPeerRoutesMethodInfo a signature where
    overloadedMethod = settingWireGuardGetPeerRoutes

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


#endif

-- method SettingWireGuard::get_peers_len
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , 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_wireguard_get_peers_len" nm_setting_wireguard_get_peers_len :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO Word32

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetPeersLen ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> m Word32
    -- ^ __Returns:__ the number of registered peers.
settingWireGuardGetPeersLen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Word32
settingWireGuardGetPeersLen a
self = 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 SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word32
result <- Ptr SettingWireGuard -> IO Word32
nm_setting_wireguard_get_peers_len Ptr SettingWireGuard
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetPeersLenMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetPeersLenMethodInfo a signature where
    overloadedMethod = settingWireGuardGetPeersLen

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


#endif

-- method SettingWireGuard::get_private_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , 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_wireguard_get_private_key" nm_setting_wireguard_get_private_key :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO CString

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetPrivateKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> m T.Text
    -- ^ __Returns:__ the set private-key or 'P.Nothing'.
settingWireGuardGetPrivateKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m Text
settingWireGuardGetPrivateKey a
self = 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 SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr SettingWireGuard -> IO CString
nm_setting_wireguard_get_private_key Ptr SettingWireGuard
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingWireGuardGetPrivateKey" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetPrivateKeyMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetPrivateKeyMethodInfo a signature where
    overloadedMethod = settingWireGuardGetPrivateKey

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


#endif

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

foreign import ccall "nm_setting_wireguard_get_private_key_flags" nm_setting_wireguard_get_private_key_flags :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    IO CUInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardGetPrivateKeyFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> m [NM.Flags.SettingSecretFlags]
    -- ^ __Returns:__ the secret-flags for [SettingWireGuard:privateKey]("GI.NM.Objects.SettingWireGuard#g:attr:privateKey").
settingWireGuardGetPrivateKeyFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> m [SettingSecretFlags]
settingWireGuardGetPrivateKeyFlags a
self = IO [SettingSecretFlags] -> m [SettingSecretFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [SettingSecretFlags] -> m [SettingSecretFlags])
-> IO [SettingSecretFlags] -> m [SettingSecretFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr SettingWireGuard -> IO CUInt
nm_setting_wireguard_get_private_key_flags Ptr SettingWireGuard
self'
    let result' :: [SettingSecretFlags]
result' = CUInt -> [SettingSecretFlags]
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
self
    [SettingSecretFlags] -> IO [SettingSecretFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [SettingSecretFlags]
result'

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardGetPrivateKeyFlagsMethodInfo
instance (signature ~ (m [NM.Flags.SettingSecretFlags]), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardGetPrivateKeyFlagsMethodInfo a signature where
    overloadedMethod = settingWireGuardGetPrivateKeyFlags

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


#endif

-- method SettingWireGuard::remove_peer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "idx"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index to remove."
--                 , 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_wireguard_remove_peer" nm_setting_wireguard_remove_peer :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    Word32 ->                               -- idx : TBasicType TUInt
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.16/
settingWireGuardRemovePeer ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> Word32
    -- ^ /@idx@/: the index to remove.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@idx@/ was in range and a peer
    --   was removed. Otherwise, /@self@/ is unchanged.
settingWireGuardRemovePeer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> Word32 -> m Bool
settingWireGuardRemovePeer a
self Word32
idx = 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 SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr SettingWireGuard -> Word32 -> IO CInt
nm_setting_wireguard_remove_peer Ptr SettingWireGuard
self' Word32
idx
    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
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardRemovePeerMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardRemovePeerMethodInfo a signature where
    overloadedMethod = settingWireGuardRemovePeer

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


#endif

-- method SettingWireGuard::set_peer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingWireGuard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingWireGuard instance"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WireGuardPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #NMWireGuardPeer instance to set.\n  This seals @peer and keeps a reference on the\n  instance."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "idx"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the index, in the range of 0 to the number of\n  peers (including). That means, if @idx is one past\n  the end of the number of peers, this is the same as\n  nm_setting_wireguard_append_peer(). Otherwise, the\n  peer at this index is replaced."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_wireguard_set_peer" nm_setting_wireguard_set_peer :: 
    Ptr SettingWireGuard ->                 -- self : TInterface (Name {namespace = "NM", name = "SettingWireGuard"})
    Ptr NM.WireGuardPeer.WireGuardPeer ->   -- peer : TInterface (Name {namespace = "NM", name = "WireGuardPeer"})
    Word32 ->                               -- idx : TBasicType TUInt
    IO ()

-- | If /@idx@/ is one past the last peer, the behavior is the same
-- as 'GI.NM.Objects.SettingWireGuard.settingWireGuardAppendPeer'.
-- Otherwise, the peer will be at /@idx@/ and replace the peer
-- instance at that index. Note that if a peer with the same
-- public-key exists on another index, then that peer will also
-- be replaced. In that case, the number of peers will shrink
-- by one (because the one at /@idx@/ got replace and then one
-- with the same public-key got removed). This also means,
-- that the resulting index afterwards may be one less than
-- /@idx@/ (if another peer with a lower index was dropped).
-- 
-- /Since: 1.16/
settingWireGuardSetPeer ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingWireGuard a) =>
    a
    -- ^ /@self@/: the t'GI.NM.Objects.SettingWireGuard.SettingWireGuard' instance
    -> NM.WireGuardPeer.WireGuardPeer
    -- ^ /@peer@/: the t'GI.NM.Structs.WireGuardPeer.WireGuardPeer' instance to set.
    --   This seals /@peer@/ and keeps a reference on the
    --   instance.
    -> Word32
    -- ^ /@idx@/: the index, in the range of 0 to the number of
    --   peers (including). That means, if /@idx@/ is one past
    --   the end of the number of peers, this is the same as
    --   'GI.NM.Objects.SettingWireGuard.settingWireGuardAppendPeer'. Otherwise, the
    --   peer at this index is replaced.
    -> m ()
settingWireGuardSetPeer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingWireGuard a) =>
a -> WireGuardPeer -> Word32 -> m ()
settingWireGuardSetPeer a
self WireGuardPeer
peer Word32
idx = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingWireGuard
self' <- a -> IO (Ptr SettingWireGuard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr WireGuardPeer
peer' <- WireGuardPeer -> IO (Ptr WireGuardPeer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WireGuardPeer
peer
    Ptr SettingWireGuard -> Ptr WireGuardPeer -> Word32 -> IO ()
nm_setting_wireguard_set_peer Ptr SettingWireGuard
self' Ptr WireGuardPeer
peer' Word32
idx
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    WireGuardPeer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WireGuardPeer
peer
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingWireGuardSetPeerMethodInfo
instance (signature ~ (NM.WireGuardPeer.WireGuardPeer -> Word32 -> m ()), MonadIO m, IsSettingWireGuard a) => O.OverloadedMethod SettingWireGuardSetPeerMethodInfo a signature where
    overloadedMethod = settingWireGuardSetPeer

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


#endif