{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.NM.Objects.DeviceVxlan
(
DeviceVxlan(..) ,
IsDeviceVxlan ,
toDeviceVxlan ,
#if defined(ENABLE_OVERLOADING)
ResolveDeviceVxlanMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetAgeingMethodInfo ,
#endif
deviceVxlanGetAgeing ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetCarrierMethodInfo ,
#endif
deviceVxlanGetCarrier ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetDstPortMethodInfo ,
#endif
deviceVxlanGetDstPort ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetGroupMethodInfo ,
#endif
deviceVxlanGetGroup ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetIdMethodInfo ,
#endif
deviceVxlanGetId ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetL2missMethodInfo ,
#endif
deviceVxlanGetL2miss ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetL3missMethodInfo ,
#endif
deviceVxlanGetL3miss ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetLearningMethodInfo ,
#endif
deviceVxlanGetLearning ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetLimitMethodInfo ,
#endif
deviceVxlanGetLimit ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetLocalMethodInfo ,
#endif
deviceVxlanGetLocal ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetParentMethodInfo ,
#endif
deviceVxlanGetParent ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetProxyMethodInfo ,
#endif
deviceVxlanGetProxy ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetRscMethodInfo ,
#endif
deviceVxlanGetRsc ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetSrcPortMaxMethodInfo ,
#endif
deviceVxlanGetSrcPortMax ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetSrcPortMinMethodInfo ,
#endif
deviceVxlanGetSrcPortMin ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetTosMethodInfo ,
#endif
deviceVxlanGetTos ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGetTtlMethodInfo ,
#endif
deviceVxlanGetTtl ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanAgeingPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanAgeing ,
#endif
getDeviceVxlanAgeing ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanCarrierPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanCarrier ,
#endif
getDeviceVxlanCarrier ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanDstPortPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanDstPort ,
#endif
getDeviceVxlanDstPort ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanGroupPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanGroup ,
#endif
getDeviceVxlanGroup ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanIdPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanId ,
#endif
getDeviceVxlanId ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanL2missPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanL2miss ,
#endif
getDeviceVxlanL2miss ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanL3missPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanL3miss ,
#endif
getDeviceVxlanL3miss ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanLearningPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanLearning ,
#endif
getDeviceVxlanLearning ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanLimitPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanLimit ,
#endif
getDeviceVxlanLimit ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanLocalPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanLocal ,
#endif
getDeviceVxlanLocal ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanParentPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanParent ,
#endif
getDeviceVxlanParent ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanProxyPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanProxy ,
#endif
getDeviceVxlanProxy ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanRscPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanRsc ,
#endif
getDeviceVxlanRsc ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanSrcPortMaxPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanSrcPortMax ,
#endif
getDeviceVxlanSrcPortMax ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanSrcPortMinPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanSrcPortMin ,
#endif
getDeviceVxlanSrcPortMin ,
#if defined(ENABLE_OVERLOADING)
DeviceVxlanTosPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanTos ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceVxlanTtlPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanTtl ,
#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
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.MainContext as GLib.MainContext
import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncInitable as Gio.AsyncInitable
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.DBusConnection as Gio.DBusConnection
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.ActiveConnection as NM.ActiveConnection
import {-# SOURCE #-} qualified GI.NM.Objects.Checkpoint as NM.Checkpoint
import {-# SOURCE #-} qualified GI.NM.Objects.Client as NM.Client
import {-# SOURCE #-} qualified GI.NM.Objects.Device as NM.Device
import {-# SOURCE #-} qualified GI.NM.Objects.DhcpConfig as NM.DhcpConfig
import {-# SOURCE #-} qualified GI.NM.Objects.IPConfig as NM.IPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.Object as NM.Object
import {-# SOURCE #-} qualified GI.NM.Objects.RemoteConnection as NM.RemoteConnection
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.DnsEntry as NM.DnsEntry
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.LldpNeighbor as NM.LldpNeighbor
import {-# SOURCE #-} qualified GI.NM.Structs.Range as NM.Range
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.NM.Objects.Device as NM.Device
import {-# SOURCE #-} qualified GI.NM.Objects.Object as NM.Object
#endif
newtype DeviceVxlan = DeviceVxlan (SP.ManagedPtr DeviceVxlan)
deriving (DeviceVxlan -> DeviceVxlan -> Bool
(DeviceVxlan -> DeviceVxlan -> Bool)
-> (DeviceVxlan -> DeviceVxlan -> Bool) -> Eq DeviceVxlan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeviceVxlan -> DeviceVxlan -> Bool
== :: DeviceVxlan -> DeviceVxlan -> Bool
$c/= :: DeviceVxlan -> DeviceVxlan -> Bool
/= :: DeviceVxlan -> DeviceVxlan -> Bool
Eq)
instance SP.ManagedPtrNewtype DeviceVxlan where
toManagedPtr :: DeviceVxlan -> ManagedPtr DeviceVxlan
toManagedPtr (DeviceVxlan ManagedPtr DeviceVxlan
p) = ManagedPtr DeviceVxlan
p
foreign import ccall "nm_device_vxlan_get_type"
c_nm_device_vxlan_get_type :: IO B.Types.GType
instance B.Types.TypedObject DeviceVxlan where
glibType :: IO GType
glibType = IO GType
c_nm_device_vxlan_get_type
instance B.Types.GObject DeviceVxlan
class (SP.GObject o, O.IsDescendantOf DeviceVxlan o) => IsDeviceVxlan o
instance (SP.GObject o, O.IsDescendantOf DeviceVxlan o) => IsDeviceVxlan o
instance O.HasParentTypes DeviceVxlan
type instance O.ParentTypes DeviceVxlan = '[NM.Device.Device, NM.Object.Object, GObject.Object.Object]
toDeviceVxlan :: (MIO.MonadIO m, IsDeviceVxlan o) => o -> m DeviceVxlan
toDeviceVxlan :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceVxlan o) =>
o -> m DeviceVxlan
toDeviceVxlan = IO DeviceVxlan -> m DeviceVxlan
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DeviceVxlan -> m DeviceVxlan)
-> (o -> IO DeviceVxlan) -> o -> m DeviceVxlan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DeviceVxlan -> DeviceVxlan) -> o -> IO DeviceVxlan
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DeviceVxlan -> DeviceVxlan
DeviceVxlan
instance B.GValue.IsGValue (Maybe DeviceVxlan) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_nm_device_vxlan_get_type
gvalueSet_ :: Ptr GValue -> Maybe DeviceVxlan -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DeviceVxlan
P.Nothing = Ptr GValue -> Ptr DeviceVxlan -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DeviceVxlan
forall a. Ptr a
FP.nullPtr :: FP.Ptr DeviceVxlan)
gvalueSet_ Ptr GValue
gv (P.Just DeviceVxlan
obj) = DeviceVxlan -> (Ptr DeviceVxlan -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DeviceVxlan
obj (Ptr GValue -> Ptr DeviceVxlan -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DeviceVxlan)
gvalueGet_ Ptr GValue
gv = do
Ptr DeviceVxlan
ptr <- Ptr GValue -> IO (Ptr DeviceVxlan)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DeviceVxlan)
if Ptr DeviceVxlan
ptr Ptr DeviceVxlan -> Ptr DeviceVxlan -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DeviceVxlan
forall a. Ptr a
FP.nullPtr
then DeviceVxlan -> Maybe DeviceVxlan
forall a. a -> Maybe a
P.Just (DeviceVxlan -> Maybe DeviceVxlan)
-> IO DeviceVxlan -> IO (Maybe DeviceVxlan)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DeviceVxlan -> DeviceVxlan)
-> Ptr DeviceVxlan -> IO DeviceVxlan
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DeviceVxlan -> DeviceVxlan
DeviceVxlan Ptr DeviceVxlan
ptr
else Maybe DeviceVxlan -> IO (Maybe DeviceVxlan)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeviceVxlan
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceVxlanMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDeviceVxlanMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDeviceVxlanMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDeviceVxlanMethod "connectionCompatible" o = NM.Device.DeviceConnectionCompatibleMethodInfo
ResolveDeviceVxlanMethod "connectionValid" o = NM.Device.DeviceConnectionValidMethodInfo
ResolveDeviceVxlanMethod "delete" o = NM.Device.DeviceDeleteMethodInfo
ResolveDeviceVxlanMethod "deleteAsync" o = NM.Device.DeviceDeleteAsyncMethodInfo
ResolveDeviceVxlanMethod "deleteFinish" o = NM.Device.DeviceDeleteFinishMethodInfo
ResolveDeviceVxlanMethod "disconnect" o = NM.Device.DeviceDisconnectMethodInfo
ResolveDeviceVxlanMethod "disconnectAsync" o = NM.Device.DeviceDisconnectAsyncMethodInfo
ResolveDeviceVxlanMethod "disconnectFinish" o = NM.Device.DeviceDisconnectFinishMethodInfo
ResolveDeviceVxlanMethod "filterConnections" o = NM.Device.DeviceFilterConnectionsMethodInfo
ResolveDeviceVxlanMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDeviceVxlanMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDeviceVxlanMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDeviceVxlanMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDeviceVxlanMethod "isReal" o = NM.Device.DeviceIsRealMethodInfo
ResolveDeviceVxlanMethod "isSoftware" o = NM.Device.DeviceIsSoftwareMethodInfo
ResolveDeviceVxlanMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDeviceVxlanMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDeviceVxlanMethod "reapply" o = NM.Device.DeviceReapplyMethodInfo
ResolveDeviceVxlanMethod "reapplyAsync" o = NM.Device.DeviceReapplyAsyncMethodInfo
ResolveDeviceVxlanMethod "reapplyFinish" o = NM.Device.DeviceReapplyFinishMethodInfo
ResolveDeviceVxlanMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDeviceVxlanMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDeviceVxlanMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDeviceVxlanMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDeviceVxlanMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDeviceVxlanMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDeviceVxlanMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDeviceVxlanMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDeviceVxlanMethod "getActiveConnection" o = NM.Device.DeviceGetActiveConnectionMethodInfo
ResolveDeviceVxlanMethod "getAgeing" o = DeviceVxlanGetAgeingMethodInfo
ResolveDeviceVxlanMethod "getAppliedConnection" o = NM.Device.DeviceGetAppliedConnectionMethodInfo
ResolveDeviceVxlanMethod "getAppliedConnectionAsync" o = NM.Device.DeviceGetAppliedConnectionAsyncMethodInfo
ResolveDeviceVxlanMethod "getAppliedConnectionFinish" o = NM.Device.DeviceGetAppliedConnectionFinishMethodInfo
ResolveDeviceVxlanMethod "getAutoconnect" o = NM.Device.DeviceGetAutoconnectMethodInfo
ResolveDeviceVxlanMethod "getAvailableConnections" o = NM.Device.DeviceGetAvailableConnectionsMethodInfo
ResolveDeviceVxlanMethod "getCapabilities" o = NM.Device.DeviceGetCapabilitiesMethodInfo
ResolveDeviceVxlanMethod "getCarrier" o = DeviceVxlanGetCarrierMethodInfo
ResolveDeviceVxlanMethod "getClient" o = NM.Object.ObjectGetClientMethodInfo
ResolveDeviceVxlanMethod "getConnectivity" o = NM.Device.DeviceGetConnectivityMethodInfo
ResolveDeviceVxlanMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDeviceVxlanMethod "getDescription" o = NM.Device.DeviceGetDescriptionMethodInfo
ResolveDeviceVxlanMethod "getDeviceType" o = NM.Device.DeviceGetDeviceTypeMethodInfo
ResolveDeviceVxlanMethod "getDhcp4Config" o = NM.Device.DeviceGetDhcp4ConfigMethodInfo
ResolveDeviceVxlanMethod "getDhcp6Config" o = NM.Device.DeviceGetDhcp6ConfigMethodInfo
ResolveDeviceVxlanMethod "getDriver" o = NM.Device.DeviceGetDriverMethodInfo
ResolveDeviceVxlanMethod "getDriverVersion" o = NM.Device.DeviceGetDriverVersionMethodInfo
ResolveDeviceVxlanMethod "getDstPort" o = DeviceVxlanGetDstPortMethodInfo
ResolveDeviceVxlanMethod "getFirmwareMissing" o = NM.Device.DeviceGetFirmwareMissingMethodInfo
ResolveDeviceVxlanMethod "getFirmwareVersion" o = NM.Device.DeviceGetFirmwareVersionMethodInfo
ResolveDeviceVxlanMethod "getGroup" o = DeviceVxlanGetGroupMethodInfo
ResolveDeviceVxlanMethod "getHwAddress" o = NM.Device.DeviceGetHwAddressMethodInfo
ResolveDeviceVxlanMethod "getId" o = DeviceVxlanGetIdMethodInfo
ResolveDeviceVxlanMethod "getIface" o = NM.Device.DeviceGetIfaceMethodInfo
ResolveDeviceVxlanMethod "getInterfaceFlags" o = NM.Device.DeviceGetInterfaceFlagsMethodInfo
ResolveDeviceVxlanMethod "getIp4Config" o = NM.Device.DeviceGetIp4ConfigMethodInfo
ResolveDeviceVxlanMethod "getIp6Config" o = NM.Device.DeviceGetIp6ConfigMethodInfo
ResolveDeviceVxlanMethod "getIpIface" o = NM.Device.DeviceGetIpIfaceMethodInfo
ResolveDeviceVxlanMethod "getL2miss" o = DeviceVxlanGetL2missMethodInfo
ResolveDeviceVxlanMethod "getL3miss" o = DeviceVxlanGetL3missMethodInfo
ResolveDeviceVxlanMethod "getLearning" o = DeviceVxlanGetLearningMethodInfo
ResolveDeviceVxlanMethod "getLimit" o = DeviceVxlanGetLimitMethodInfo
ResolveDeviceVxlanMethod "getLldpNeighbors" o = NM.Device.DeviceGetLldpNeighborsMethodInfo
ResolveDeviceVxlanMethod "getLocal" o = DeviceVxlanGetLocalMethodInfo
ResolveDeviceVxlanMethod "getManaged" o = NM.Device.DeviceGetManagedMethodInfo
ResolveDeviceVxlanMethod "getMetered" o = NM.Device.DeviceGetMeteredMethodInfo
ResolveDeviceVxlanMethod "getMtu" o = NM.Device.DeviceGetMtuMethodInfo
ResolveDeviceVxlanMethod "getNmPluginMissing" o = NM.Device.DeviceGetNmPluginMissingMethodInfo
ResolveDeviceVxlanMethod "getParent" o = DeviceVxlanGetParentMethodInfo
ResolveDeviceVxlanMethod "getPath" o = NM.Device.DeviceGetPathMethodInfo
ResolveDeviceVxlanMethod "getPhysicalPortId" o = NM.Device.DeviceGetPhysicalPortIdMethodInfo
ResolveDeviceVxlanMethod "getPorts" o = NM.Device.DeviceGetPortsMethodInfo
ResolveDeviceVxlanMethod "getProduct" o = NM.Device.DeviceGetProductMethodInfo
ResolveDeviceVxlanMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDeviceVxlanMethod "getProxy" o = DeviceVxlanGetProxyMethodInfo
ResolveDeviceVxlanMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDeviceVxlanMethod "getRsc" o = DeviceVxlanGetRscMethodInfo
ResolveDeviceVxlanMethod "getSettingType" o = NM.Device.DeviceGetSettingTypeMethodInfo
ResolveDeviceVxlanMethod "getSrcPortMax" o = DeviceVxlanGetSrcPortMaxMethodInfo
ResolveDeviceVxlanMethod "getSrcPortMin" o = DeviceVxlanGetSrcPortMinMethodInfo
ResolveDeviceVxlanMethod "getState" o = NM.Device.DeviceGetStateMethodInfo
ResolveDeviceVxlanMethod "getStateReason" o = NM.Device.DeviceGetStateReasonMethodInfo
ResolveDeviceVxlanMethod "getTos" o = DeviceVxlanGetTosMethodInfo
ResolveDeviceVxlanMethod "getTtl" o = DeviceVxlanGetTtlMethodInfo
ResolveDeviceVxlanMethod "getTypeDescription" o = NM.Device.DeviceGetTypeDescriptionMethodInfo
ResolveDeviceVxlanMethod "getUdi" o = NM.Device.DeviceGetUdiMethodInfo
ResolveDeviceVxlanMethod "getVendor" o = NM.Device.DeviceGetVendorMethodInfo
ResolveDeviceVxlanMethod "setAutoconnect" o = NM.Device.DeviceSetAutoconnectMethodInfo
ResolveDeviceVxlanMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDeviceVxlanMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDeviceVxlanMethod "setManaged" o = NM.Device.DeviceSetManagedMethodInfo
ResolveDeviceVxlanMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDeviceVxlanMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDeviceVxlanMethod t DeviceVxlan, O.OverloadedMethod info DeviceVxlan p) => OL.IsLabel t (DeviceVxlan -> 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 ~ ResolveDeviceVxlanMethod t DeviceVxlan, O.OverloadedMethod info DeviceVxlan p, R.HasField t DeviceVxlan p) => R.HasField t DeviceVxlan p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDeviceVxlanMethod t DeviceVxlan, O.OverloadedMethodInfo info DeviceVxlan) => OL.IsLabel t (O.MethodProxy info DeviceVxlan) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getDeviceVxlanAgeing :: (MonadIO m, IsDeviceVxlan o) => o -> m Word32
getDeviceVxlanAgeing :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceVxlan o) =>
o -> m Word32
getDeviceVxlanAgeing o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"ageing"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanAgeingPropertyInfo
instance AttrInfo DeviceVxlanAgeingPropertyInfo where
type AttrAllowedOps DeviceVxlanAgeingPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanAgeingPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanAgeingPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanAgeingPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanAgeingPropertyInfo = ()
type AttrGetType DeviceVxlanAgeingPropertyInfo = Word32
type AttrLabel DeviceVxlanAgeingPropertyInfo = "ageing"
type AttrOrigin DeviceVxlanAgeingPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanAgeing
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.ageing"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:ageing"
})
#endif
getDeviceVxlanCarrier :: (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanCarrier :: forall (m :: * -> *) o. (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanCarrier 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
"carrier"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanCarrierPropertyInfo
instance AttrInfo DeviceVxlanCarrierPropertyInfo where
type AttrAllowedOps DeviceVxlanCarrierPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanCarrierPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanCarrierPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanCarrierPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanCarrierPropertyInfo = ()
type AttrGetType DeviceVxlanCarrierPropertyInfo = Bool
type AttrLabel DeviceVxlanCarrierPropertyInfo = "carrier"
type AttrOrigin DeviceVxlanCarrierPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanCarrier
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.carrier"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:carrier"
})
#endif
getDeviceVxlanDstPort :: (MonadIO m, IsDeviceVxlan o) => o -> m Word32
getDeviceVxlanDstPort :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceVxlan o) =>
o -> m Word32
getDeviceVxlanDstPort 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
"dst-port"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanDstPortPropertyInfo
instance AttrInfo DeviceVxlanDstPortPropertyInfo where
type AttrAllowedOps DeviceVxlanDstPortPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanDstPortPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanDstPortPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanDstPortPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanDstPortPropertyInfo = ()
type AttrGetType DeviceVxlanDstPortPropertyInfo = Word32
type AttrLabel DeviceVxlanDstPortPropertyInfo = "dst-port"
type AttrOrigin DeviceVxlanDstPortPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanDstPort
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.dstPort"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:dstPort"
})
#endif
getDeviceVxlanGroup :: (MonadIO m, IsDeviceVxlan o) => o -> m T.Text
getDeviceVxlanGroup :: forall (m :: * -> *) o. (MonadIO m, IsDeviceVxlan o) => o -> m Text
getDeviceVxlanGroup 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
"getDeviceVxlanGroup" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"group"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGroupPropertyInfo
instance AttrInfo DeviceVxlanGroupPropertyInfo where
type AttrAllowedOps DeviceVxlanGroupPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceVxlanGroupPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanGroupPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanGroupPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanGroupPropertyInfo = ()
type AttrGetType DeviceVxlanGroupPropertyInfo = T.Text
type AttrLabel DeviceVxlanGroupPropertyInfo = "group"
type AttrOrigin DeviceVxlanGroupPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanGroup
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.group"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:group"
})
#endif
getDeviceVxlanId :: (MonadIO m, IsDeviceVxlan o) => o -> m Word32
getDeviceVxlanId :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceVxlan o) =>
o -> m Word32
getDeviceVxlanId o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"id"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanIdPropertyInfo
instance AttrInfo DeviceVxlanIdPropertyInfo where
type AttrAllowedOps DeviceVxlanIdPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanIdPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanIdPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanIdPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanIdPropertyInfo = ()
type AttrGetType DeviceVxlanIdPropertyInfo = Word32
type AttrLabel DeviceVxlanIdPropertyInfo = "id"
type AttrOrigin DeviceVxlanIdPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanId
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.id"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:id"
})
#endif
getDeviceVxlanL2miss :: (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanL2miss :: forall (m :: * -> *) o. (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanL2miss 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
"l2miss"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanL2missPropertyInfo
instance AttrInfo DeviceVxlanL2missPropertyInfo where
type AttrAllowedOps DeviceVxlanL2missPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanL2missPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanL2missPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanL2missPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanL2missPropertyInfo = ()
type AttrGetType DeviceVxlanL2missPropertyInfo = Bool
type AttrLabel DeviceVxlanL2missPropertyInfo = "l2miss"
type AttrOrigin DeviceVxlanL2missPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanL2miss
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.l2miss"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:l2miss"
})
#endif
getDeviceVxlanL3miss :: (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanL3miss :: forall (m :: * -> *) o. (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanL3miss 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
"l3miss"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanL3missPropertyInfo
instance AttrInfo DeviceVxlanL3missPropertyInfo where
type AttrAllowedOps DeviceVxlanL3missPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanL3missPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanL3missPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanL3missPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanL3missPropertyInfo = ()
type AttrGetType DeviceVxlanL3missPropertyInfo = Bool
type AttrLabel DeviceVxlanL3missPropertyInfo = "l3miss"
type AttrOrigin DeviceVxlanL3missPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanL3miss
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.l3miss"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:l3miss"
})
#endif
getDeviceVxlanLearning :: (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanLearning :: forall (m :: * -> *) o. (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanLearning o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"learning"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanLearningPropertyInfo
instance AttrInfo DeviceVxlanLearningPropertyInfo where
type AttrAllowedOps DeviceVxlanLearningPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanLearningPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanLearningPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanLearningPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanLearningPropertyInfo = ()
type AttrGetType DeviceVxlanLearningPropertyInfo = Bool
type AttrLabel DeviceVxlanLearningPropertyInfo = "learning"
type AttrOrigin DeviceVxlanLearningPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanLearning
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.learning"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:learning"
})
#endif
getDeviceVxlanLimit :: (MonadIO m, IsDeviceVxlan o) => o -> m Word32
getDeviceVxlanLimit :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceVxlan o) =>
o -> m Word32
getDeviceVxlanLimit o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"limit"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanLimitPropertyInfo
instance AttrInfo DeviceVxlanLimitPropertyInfo where
type AttrAllowedOps DeviceVxlanLimitPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanLimitPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanLimitPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanLimitPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanLimitPropertyInfo = ()
type AttrGetType DeviceVxlanLimitPropertyInfo = Word32
type AttrLabel DeviceVxlanLimitPropertyInfo = "limit"
type AttrOrigin DeviceVxlanLimitPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanLimit
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.limit"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:limit"
})
#endif
getDeviceVxlanLocal :: (MonadIO m, IsDeviceVxlan o) => o -> m T.Text
getDeviceVxlanLocal :: forall (m :: * -> *) o. (MonadIO m, IsDeviceVxlan o) => o -> m Text
getDeviceVxlanLocal 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
"getDeviceVxlanLocal" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"local"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanLocalPropertyInfo
instance AttrInfo DeviceVxlanLocalPropertyInfo where
type AttrAllowedOps DeviceVxlanLocalPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceVxlanLocalPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanLocalPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanLocalPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanLocalPropertyInfo = ()
type AttrGetType DeviceVxlanLocalPropertyInfo = T.Text
type AttrLabel DeviceVxlanLocalPropertyInfo = "local"
type AttrOrigin DeviceVxlanLocalPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanLocal
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.local"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:local"
})
#endif
getDeviceVxlanParent :: (MonadIO m, IsDeviceVxlan o) => o -> m NM.Device.Device
getDeviceVxlanParent :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceVxlan o) =>
o -> m Device
getDeviceVxlanParent o
obj = IO Device -> m Device
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Device -> m Device) -> IO Device -> m Device
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Device) -> IO Device
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDeviceVxlanParent" (IO (Maybe Device) -> IO Device) -> IO (Maybe Device) -> IO Device
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Device -> Device) -> IO (Maybe Device)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"parent" ManagedPtr Device -> Device
NM.Device.Device
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanParentPropertyInfo
instance AttrInfo DeviceVxlanParentPropertyInfo where
type AttrAllowedOps DeviceVxlanParentPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceVxlanParentPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanParentPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanParentPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanParentPropertyInfo = ()
type AttrGetType DeviceVxlanParentPropertyInfo = NM.Device.Device
type AttrLabel DeviceVxlanParentPropertyInfo = "parent"
type AttrOrigin DeviceVxlanParentPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanParent
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.parent"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:parent"
})
#endif
getDeviceVxlanProxy :: (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanProxy :: forall (m :: * -> *) o. (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanProxy o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"proxy"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanProxyPropertyInfo
instance AttrInfo DeviceVxlanProxyPropertyInfo where
type AttrAllowedOps DeviceVxlanProxyPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanProxyPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanProxyPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanProxyPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanProxyPropertyInfo = ()
type AttrGetType DeviceVxlanProxyPropertyInfo = Bool
type AttrLabel DeviceVxlanProxyPropertyInfo = "proxy"
type AttrOrigin DeviceVxlanProxyPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanProxy
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.proxy"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:proxy"
})
#endif
getDeviceVxlanRsc :: (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanRsc :: forall (m :: * -> *) o. (MonadIO m, IsDeviceVxlan o) => o -> m Bool
getDeviceVxlanRsc o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"rsc"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanRscPropertyInfo
instance AttrInfo DeviceVxlanRscPropertyInfo where
type AttrAllowedOps DeviceVxlanRscPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanRscPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanRscPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanRscPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanRscPropertyInfo = ()
type AttrGetType DeviceVxlanRscPropertyInfo = Bool
type AttrLabel DeviceVxlanRscPropertyInfo = "rsc"
type AttrOrigin DeviceVxlanRscPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanRsc
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.rsc"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:rsc"
})
#endif
getDeviceVxlanSrcPortMax :: (MonadIO m, IsDeviceVxlan o) => o -> m Word32
getDeviceVxlanSrcPortMax :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceVxlan o) =>
o -> m Word32
getDeviceVxlanSrcPortMax 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
"src-port-max"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanSrcPortMaxPropertyInfo
instance AttrInfo DeviceVxlanSrcPortMaxPropertyInfo where
type AttrAllowedOps DeviceVxlanSrcPortMaxPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanSrcPortMaxPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanSrcPortMaxPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanSrcPortMaxPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanSrcPortMaxPropertyInfo = ()
type AttrGetType DeviceVxlanSrcPortMaxPropertyInfo = Word32
type AttrLabel DeviceVxlanSrcPortMaxPropertyInfo = "src-port-max"
type AttrOrigin DeviceVxlanSrcPortMaxPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanSrcPortMax
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.srcPortMax"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:srcPortMax"
})
#endif
getDeviceVxlanSrcPortMin :: (MonadIO m, IsDeviceVxlan o) => o -> m Word32
getDeviceVxlanSrcPortMin :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceVxlan o) =>
o -> m Word32
getDeviceVxlanSrcPortMin 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
"src-port-min"
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanSrcPortMinPropertyInfo
instance AttrInfo DeviceVxlanSrcPortMinPropertyInfo where
type AttrAllowedOps DeviceVxlanSrcPortMinPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceVxlanSrcPortMinPropertyInfo = IsDeviceVxlan
type AttrSetTypeConstraint DeviceVxlanSrcPortMinPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanSrcPortMinPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanSrcPortMinPropertyInfo = ()
type AttrGetType DeviceVxlanSrcPortMinPropertyInfo = Word32
type AttrLabel DeviceVxlanSrcPortMinPropertyInfo = "src-port-min"
type AttrOrigin DeviceVxlanSrcPortMinPropertyInfo = DeviceVxlan
attrGet = getDeviceVxlanSrcPortMin
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.srcPortMin"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#g:attr:srcPortMin"
})
#endif
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanTosPropertyInfo
instance AttrInfo DeviceVxlanTosPropertyInfo where
type AttrAllowedOps DeviceVxlanTosPropertyInfo = '[]
type AttrSetTypeConstraint DeviceVxlanTosPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanTosPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanTosPropertyInfo = ()
type AttrBaseTypeConstraint DeviceVxlanTosPropertyInfo = (~) ()
type AttrGetType DeviceVxlanTosPropertyInfo = ()
type AttrLabel DeviceVxlanTosPropertyInfo = ""
type AttrOrigin DeviceVxlanTosPropertyInfo = DeviceVxlan
attrGet = undefined
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
#endif
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanTtlPropertyInfo
instance AttrInfo DeviceVxlanTtlPropertyInfo where
type AttrAllowedOps DeviceVxlanTtlPropertyInfo = '[]
type AttrSetTypeConstraint DeviceVxlanTtlPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceVxlanTtlPropertyInfo = (~) ()
type AttrTransferType DeviceVxlanTtlPropertyInfo = ()
type AttrBaseTypeConstraint DeviceVxlanTtlPropertyInfo = (~) ()
type AttrGetType DeviceVxlanTtlPropertyInfo = ()
type AttrLabel DeviceVxlanTtlPropertyInfo = ""
type AttrOrigin DeviceVxlanTtlPropertyInfo = DeviceVxlan
attrGet = undefined
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DeviceVxlan
type instance O.AttributeList DeviceVxlan = DeviceVxlanAttributeList
type DeviceVxlanAttributeList = ('[ '("activeConnection", NM.Device.DeviceActiveConnectionPropertyInfo), '("ageing", DeviceVxlanAgeingPropertyInfo), '("autoconnect", NM.Device.DeviceAutoconnectPropertyInfo), '("availableConnections", NM.Device.DeviceAvailableConnectionsPropertyInfo), '("capabilities", NM.Device.DeviceCapabilitiesPropertyInfo), '("carrier", DeviceVxlanCarrierPropertyInfo), '("client", NM.Object.ObjectClientPropertyInfo), '("deviceType", NM.Device.DeviceDeviceTypePropertyInfo), '("dhcp4Config", NM.Device.DeviceDhcp4ConfigPropertyInfo), '("dhcp6Config", NM.Device.DeviceDhcp6ConfigPropertyInfo), '("driver", NM.Device.DeviceDriverPropertyInfo), '("driverVersion", NM.Device.DeviceDriverVersionPropertyInfo), '("dstPort", DeviceVxlanDstPortPropertyInfo), '("firmwareMissing", NM.Device.DeviceFirmwareMissingPropertyInfo), '("firmwareVersion", NM.Device.DeviceFirmwareVersionPropertyInfo), '("group", DeviceVxlanGroupPropertyInfo), '("hwAddress", NM.Device.DeviceHwAddressPropertyInfo), '("id", DeviceVxlanIdPropertyInfo), '("interface", NM.Device.DeviceInterfacePropertyInfo), '("interfaceFlags", NM.Device.DeviceInterfaceFlagsPropertyInfo), '("ipInterface", NM.Device.DeviceIpInterfacePropertyInfo), '("ip4Config", NM.Device.DeviceIp4ConfigPropertyInfo), '("ip4Connectivity", NM.Device.DeviceIp4ConnectivityPropertyInfo), '("ip6Config", NM.Device.DeviceIp6ConfigPropertyInfo), '("ip6Connectivity", NM.Device.DeviceIp6ConnectivityPropertyInfo), '("l2miss", DeviceVxlanL2missPropertyInfo), '("l3miss", DeviceVxlanL3missPropertyInfo), '("learning", DeviceVxlanLearningPropertyInfo), '("limit", DeviceVxlanLimitPropertyInfo), '("lldpNeighbors", NM.Device.DeviceLldpNeighborsPropertyInfo), '("local", DeviceVxlanLocalPropertyInfo), '("managed", NM.Device.DeviceManagedPropertyInfo), '("metered", NM.Device.DeviceMeteredPropertyInfo), '("mtu", NM.Device.DeviceMtuPropertyInfo), '("nmPluginMissing", NM.Device.DeviceNmPluginMissingPropertyInfo), '("parent", DeviceVxlanParentPropertyInfo), '("path", NM.Device.DevicePathPropertyInfo), '("physicalPortId", NM.Device.DevicePhysicalPortIdPropertyInfo), '("ports", NM.Device.DevicePortsPropertyInfo), '("product", NM.Device.DeviceProductPropertyInfo), '("proxy", DeviceVxlanProxyPropertyInfo), '("real", NM.Device.DeviceRealPropertyInfo), '("rsc", DeviceVxlanRscPropertyInfo), '("srcPortMax", DeviceVxlanSrcPortMaxPropertyInfo), '("srcPortMin", DeviceVxlanSrcPortMinPropertyInfo), '("state", NM.Device.DeviceStatePropertyInfo), '("stateReason", NM.Device.DeviceStateReasonPropertyInfo), '("tos", DeviceVxlanTosPropertyInfo), '("ttl", DeviceVxlanTtlPropertyInfo), '("udi", NM.Device.DeviceUdiPropertyInfo), '("vendor", NM.Device.DeviceVendorPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
deviceVxlanAgeing :: AttrLabelProxy "ageing"
deviceVxlanAgeing = AttrLabelProxy
deviceVxlanCarrier :: AttrLabelProxy "carrier"
deviceVxlanCarrier = AttrLabelProxy
deviceVxlanDstPort :: AttrLabelProxy "dstPort"
deviceVxlanDstPort = AttrLabelProxy
deviceVxlanGroup :: AttrLabelProxy "group"
deviceVxlanGroup = AttrLabelProxy
deviceVxlanId :: AttrLabelProxy "id"
deviceVxlanId = AttrLabelProxy
deviceVxlanL2miss :: AttrLabelProxy "l2miss"
deviceVxlanL2miss = AttrLabelProxy
deviceVxlanL3miss :: AttrLabelProxy "l3miss"
deviceVxlanL3miss = AttrLabelProxy
deviceVxlanLearning :: AttrLabelProxy "learning"
deviceVxlanLearning = AttrLabelProxy
deviceVxlanLimit :: AttrLabelProxy "limit"
deviceVxlanLimit = AttrLabelProxy
deviceVxlanLocal :: AttrLabelProxy "local"
deviceVxlanLocal = AttrLabelProxy
deviceVxlanParent :: AttrLabelProxy "parent"
deviceVxlanParent = AttrLabelProxy
deviceVxlanProxy :: AttrLabelProxy "proxy"
deviceVxlanProxy = AttrLabelProxy
deviceVxlanRsc :: AttrLabelProxy "rsc"
deviceVxlanRsc = AttrLabelProxy
deviceVxlanSrcPortMax :: AttrLabelProxy "srcPortMax"
deviceVxlanSrcPortMax = AttrLabelProxy
deviceVxlanSrcPortMin :: AttrLabelProxy "srcPortMin"
deviceVxlanSrcPortMin = AttrLabelProxy
deviceVxlanTos :: AttrLabelProxy "tos"
deviceVxlanTos = AttrLabelProxy
deviceVxlanTtl :: AttrLabelProxy "ttl"
deviceVxlanTtl = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DeviceVxlan = DeviceVxlanSignalList
type DeviceVxlanSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("stateChanged", NM.Device.DeviceStateChangedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "nm_device_vxlan_get_ageing" nm_device_vxlan_get_ageing ::
Ptr DeviceVxlan ->
IO Word32
deviceVxlanGetAgeing ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Word32
deviceVxlanGetAgeing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Word32
deviceVxlanGetAgeing a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word32
result <- Ptr DeviceVxlan -> IO Word32
nm_device_vxlan_get_ageing Ptr DeviceVxlan
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetAgeingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetAgeingMethodInfo a signature where
overloadedMethod = deviceVxlanGetAgeing
instance O.OverloadedMethodInfo DeviceVxlanGetAgeingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetAgeing",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetAgeing"
})
#endif
foreign import ccall "nm_device_vxlan_get_carrier" nm_device_vxlan_get_carrier ::
Ptr DeviceVxlan ->
IO CInt
deviceVxlanGetCarrier ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Bool
deviceVxlanGetCarrier :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Bool
deviceVxlanGetCarrier a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CInt
result <- Ptr DeviceVxlan -> IO CInt
nm_device_vxlan_get_carrier Ptr DeviceVxlan
device'
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
device
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetCarrierMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetCarrierMethodInfo a signature where
overloadedMethod = deviceVxlanGetCarrier
instance O.OverloadedMethodInfo DeviceVxlanGetCarrierMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetCarrier",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetCarrier"
})
#endif
foreign import ccall "nm_device_vxlan_get_dst_port" nm_device_vxlan_get_dst_port ::
Ptr DeviceVxlan ->
IO Word32
deviceVxlanGetDstPort ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Word32
deviceVxlanGetDstPort :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Word32
deviceVxlanGetDstPort a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word32
result <- Ptr DeviceVxlan -> IO Word32
nm_device_vxlan_get_dst_port Ptr DeviceVxlan
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetDstPortMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetDstPortMethodInfo a signature where
overloadedMethod = deviceVxlanGetDstPort
instance O.OverloadedMethodInfo DeviceVxlanGetDstPortMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetDstPort",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetDstPort"
})
#endif
foreign import ccall "nm_device_vxlan_get_group" nm_device_vxlan_get_group ::
Ptr DeviceVxlan ->
IO CString
deviceVxlanGetGroup ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m T.Text
deviceVxlanGetGroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Text
deviceVxlanGetGroup a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CString
result <- Ptr DeviceVxlan -> IO CString
nm_device_vxlan_get_group Ptr DeviceVxlan
device'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceVxlanGetGroup" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetGroupMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetGroupMethodInfo a signature where
overloadedMethod = deviceVxlanGetGroup
instance O.OverloadedMethodInfo DeviceVxlanGetGroupMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetGroup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetGroup"
})
#endif
foreign import ccall "nm_device_vxlan_get_id" nm_device_vxlan_get_id ::
Ptr DeviceVxlan ->
IO Word32
deviceVxlanGetId ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Word32
deviceVxlanGetId :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Word32
deviceVxlanGetId a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word32
result <- Ptr DeviceVxlan -> IO Word32
nm_device_vxlan_get_id Ptr DeviceVxlan
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetIdMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetIdMethodInfo a signature where
overloadedMethod = deviceVxlanGetId
instance O.OverloadedMethodInfo DeviceVxlanGetIdMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetId",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetId"
})
#endif
foreign import ccall "nm_device_vxlan_get_l2miss" nm_device_vxlan_get_l2miss ::
Ptr DeviceVxlan ->
IO CInt
deviceVxlanGetL2miss ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Bool
deviceVxlanGetL2miss :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Bool
deviceVxlanGetL2miss a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CInt
result <- Ptr DeviceVxlan -> IO CInt
nm_device_vxlan_get_l2miss Ptr DeviceVxlan
device'
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
device
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetL2missMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetL2missMethodInfo a signature where
overloadedMethod = deviceVxlanGetL2miss
instance O.OverloadedMethodInfo DeviceVxlanGetL2missMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetL2miss",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetL2miss"
})
#endif
foreign import ccall "nm_device_vxlan_get_l3miss" nm_device_vxlan_get_l3miss ::
Ptr DeviceVxlan ->
IO CInt
deviceVxlanGetL3miss ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Bool
deviceVxlanGetL3miss :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Bool
deviceVxlanGetL3miss a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CInt
result <- Ptr DeviceVxlan -> IO CInt
nm_device_vxlan_get_l3miss Ptr DeviceVxlan
device'
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
device
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetL3missMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetL3missMethodInfo a signature where
overloadedMethod = deviceVxlanGetL3miss
instance O.OverloadedMethodInfo DeviceVxlanGetL3missMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetL3miss",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetL3miss"
})
#endif
foreign import ccall "nm_device_vxlan_get_learning" nm_device_vxlan_get_learning ::
Ptr DeviceVxlan ->
IO CInt
deviceVxlanGetLearning ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Bool
deviceVxlanGetLearning :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Bool
deviceVxlanGetLearning a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CInt
result <- Ptr DeviceVxlan -> IO CInt
nm_device_vxlan_get_learning Ptr DeviceVxlan
device'
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
device
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetLearningMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetLearningMethodInfo a signature where
overloadedMethod = deviceVxlanGetLearning
instance O.OverloadedMethodInfo DeviceVxlanGetLearningMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetLearning",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetLearning"
})
#endif
foreign import ccall "nm_device_vxlan_get_limit" nm_device_vxlan_get_limit ::
Ptr DeviceVxlan ->
IO Word32
deviceVxlanGetLimit ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Word32
deviceVxlanGetLimit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Word32
deviceVxlanGetLimit a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word32
result <- Ptr DeviceVxlan -> IO Word32
nm_device_vxlan_get_limit Ptr DeviceVxlan
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetLimitMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetLimitMethodInfo a signature where
overloadedMethod = deviceVxlanGetLimit
instance O.OverloadedMethodInfo DeviceVxlanGetLimitMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetLimit",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetLimit"
})
#endif
foreign import ccall "nm_device_vxlan_get_local" nm_device_vxlan_get_local ::
Ptr DeviceVxlan ->
IO CString
deviceVxlanGetLocal ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m T.Text
deviceVxlanGetLocal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Text
deviceVxlanGetLocal a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CString
result <- Ptr DeviceVxlan -> IO CString
nm_device_vxlan_get_local Ptr DeviceVxlan
device'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceVxlanGetLocal" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetLocalMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetLocalMethodInfo a signature where
overloadedMethod = deviceVxlanGetLocal
instance O.OverloadedMethodInfo DeviceVxlanGetLocalMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetLocal",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetLocal"
})
#endif
foreign import ccall "nm_device_vxlan_get_parent" nm_device_vxlan_get_parent ::
Ptr DeviceVxlan ->
IO (Ptr NM.Device.Device)
deviceVxlanGetParent ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m NM.Device.Device
deviceVxlanGetParent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Device
deviceVxlanGetParent a
device = IO Device -> m Device
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Device -> m Device) -> IO Device -> m Device
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr Device
result <- Ptr DeviceVxlan -> IO (Ptr Device)
nm_device_vxlan_get_parent Ptr DeviceVxlan
device'
Text -> Ptr Device -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceVxlanGetParent" Ptr Device
result
Device
result' <- ((ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Device -> Device
NM.Device.Device) Ptr Device
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Device -> IO Device
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Device
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetParentMethodInfo
instance (signature ~ (m NM.Device.Device), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetParentMethodInfo a signature where
overloadedMethod = deviceVxlanGetParent
instance O.OverloadedMethodInfo DeviceVxlanGetParentMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetParent",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetParent"
})
#endif
foreign import ccall "nm_device_vxlan_get_proxy" nm_device_vxlan_get_proxy ::
Ptr DeviceVxlan ->
IO CInt
deviceVxlanGetProxy ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Bool
deviceVxlanGetProxy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Bool
deviceVxlanGetProxy a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CInt
result <- Ptr DeviceVxlan -> IO CInt
nm_device_vxlan_get_proxy Ptr DeviceVxlan
device'
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
device
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetProxyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetProxyMethodInfo a signature where
overloadedMethod = deviceVxlanGetProxy
instance O.OverloadedMethodInfo DeviceVxlanGetProxyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetProxy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetProxy"
})
#endif
foreign import ccall "nm_device_vxlan_get_rsc" nm_device_vxlan_get_rsc ::
Ptr DeviceVxlan ->
IO CInt
deviceVxlanGetRsc ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Bool
deviceVxlanGetRsc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Bool
deviceVxlanGetRsc a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CInt
result <- Ptr DeviceVxlan -> IO CInt
nm_device_vxlan_get_rsc Ptr DeviceVxlan
device'
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
device
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetRscMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetRscMethodInfo a signature where
overloadedMethod = deviceVxlanGetRsc
instance O.OverloadedMethodInfo DeviceVxlanGetRscMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetRsc",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetRsc"
})
#endif
foreign import ccall "nm_device_vxlan_get_src_port_max" nm_device_vxlan_get_src_port_max ::
Ptr DeviceVxlan ->
IO Word32
deviceVxlanGetSrcPortMax ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Word32
deviceVxlanGetSrcPortMax :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Word32
deviceVxlanGetSrcPortMax a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word32
result <- Ptr DeviceVxlan -> IO Word32
nm_device_vxlan_get_src_port_max Ptr DeviceVxlan
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetSrcPortMaxMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetSrcPortMaxMethodInfo a signature where
overloadedMethod = deviceVxlanGetSrcPortMax
instance O.OverloadedMethodInfo DeviceVxlanGetSrcPortMaxMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetSrcPortMax",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetSrcPortMax"
})
#endif
foreign import ccall "nm_device_vxlan_get_src_port_min" nm_device_vxlan_get_src_port_min ::
Ptr DeviceVxlan ->
IO Word32
deviceVxlanGetSrcPortMin ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Word32
deviceVxlanGetSrcPortMin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Word32
deviceVxlanGetSrcPortMin a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word32
result <- Ptr DeviceVxlan -> IO Word32
nm_device_vxlan_get_src_port_min Ptr DeviceVxlan
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetSrcPortMinMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetSrcPortMinMethodInfo a signature where
overloadedMethod = deviceVxlanGetSrcPortMin
instance O.OverloadedMethodInfo DeviceVxlanGetSrcPortMinMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetSrcPortMin",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetSrcPortMin"
})
#endif
foreign import ccall "nm_device_vxlan_get_tos" nm_device_vxlan_get_tos ::
Ptr DeviceVxlan ->
IO Word32
deviceVxlanGetTos ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Word32
deviceVxlanGetTos :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Word32
deviceVxlanGetTos a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word32
result <- Ptr DeviceVxlan -> IO Word32
nm_device_vxlan_get_tos Ptr DeviceVxlan
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetTosMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetTosMethodInfo a signature where
overloadedMethod = deviceVxlanGetTos
instance O.OverloadedMethodInfo DeviceVxlanGetTosMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetTos",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetTos"
})
#endif
foreign import ccall "nm_device_vxlan_get_ttl" nm_device_vxlan_get_ttl ::
Ptr DeviceVxlan ->
IO Word32
deviceVxlanGetTtl ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a
-> m Word32
deviceVxlanGetTtl :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceVxlan a) =>
a -> m Word32
deviceVxlanGetTtl a
device = 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 DeviceVxlan
device' <- a -> IO (Ptr DeviceVxlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word32
result <- Ptr DeviceVxlan -> IO Word32
nm_device_vxlan_get_ttl Ptr DeviceVxlan
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceVxlanGetTtlMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceVxlan a) => O.OverloadedMethod DeviceVxlanGetTtlMethodInfo a signature where
overloadedMethod = deviceVxlanGetTtl
instance O.OverloadedMethodInfo DeviceVxlanGetTtlMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceVxlan.deviceVxlanGetTtl",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceVxlan.html#v:deviceVxlanGetTtl"
})
#endif