{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- SR-IOV settings
-- 
-- /Since: 1.14/

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

module GI.NM.Objects.SettingSriov
    ( 

-- * Exported types
    SettingSriov(..)                        ,
    IsSettingSriov                          ,
    toSettingSriov                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addVf]("GI.NM.Objects.SettingSriov#g:method:addVf"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clearVfs]("GI.NM.Objects.SettingSriov#g:method:clearVfs"), [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"), [removeVf]("GI.NM.Objects.SettingSriov#g:method:removeVf"), [removeVfByIndex]("GI.NM.Objects.SettingSriov#g:method:removeVfByIndex"), [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
-- [getAutoprobeDrivers]("GI.NM.Objects.SettingSriov#g:method:getAutoprobeDrivers"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDbusPropertyType]("GI.NM.Objects.Setting#g:method:getDbusPropertyType"), [getEswitchEncapMode]("GI.NM.Objects.SettingSriov#g:method:getEswitchEncapMode"), [getEswitchInlineMode]("GI.NM.Objects.SettingSriov#g:method:getEswitchInlineMode"), [getEswitchMode]("GI.NM.Objects.SettingSriov#g:method:getEswitchMode"), [getName]("GI.NM.Objects.Setting#g:method:getName"), [getNumVfs]("GI.NM.Objects.SettingSriov#g:method:getNumVfs"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSecretFlags]("GI.NM.Objects.Setting#g:method:getSecretFlags"), [getTotalVfs]("GI.NM.Objects.SettingSriov#g:method:getTotalVfs"), [getVf]("GI.NM.Objects.SettingSriov#g:method:getVf").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSecretFlags]("GI.NM.Objects.Setting#g:method:setSecretFlags").

#if defined(ENABLE_OVERLOADING)
    ResolveSettingSriovMethod               ,
#endif

-- ** addVf #method:addVf#

#if defined(ENABLE_OVERLOADING)
    SettingSriovAddVfMethodInfo             ,
#endif
    settingSriovAddVf                       ,


-- ** clearVfs #method:clearVfs#

#if defined(ENABLE_OVERLOADING)
    SettingSriovClearVfsMethodInfo          ,
#endif
    settingSriovClearVfs                    ,


-- ** getAutoprobeDrivers #method:getAutoprobeDrivers#

#if defined(ENABLE_OVERLOADING)
    SettingSriovGetAutoprobeDriversMethodInfo,
#endif
    settingSriovGetAutoprobeDrivers         ,


-- ** getEswitchEncapMode #method:getEswitchEncapMode#

#if defined(ENABLE_OVERLOADING)
    SettingSriovGetEswitchEncapModeMethodInfo,
#endif
    settingSriovGetEswitchEncapMode         ,


-- ** getEswitchInlineMode #method:getEswitchInlineMode#

#if defined(ENABLE_OVERLOADING)
    SettingSriovGetEswitchInlineModeMethodInfo,
#endif
    settingSriovGetEswitchInlineMode        ,


-- ** getEswitchMode #method:getEswitchMode#

#if defined(ENABLE_OVERLOADING)
    SettingSriovGetEswitchModeMethodInfo    ,
#endif
    settingSriovGetEswitchMode              ,


-- ** getNumVfs #method:getNumVfs#

#if defined(ENABLE_OVERLOADING)
    SettingSriovGetNumVfsMethodInfo         ,
#endif
    settingSriovGetNumVfs                   ,


-- ** getTotalVfs #method:getTotalVfs#

#if defined(ENABLE_OVERLOADING)
    SettingSriovGetTotalVfsMethodInfo       ,
#endif
    settingSriovGetTotalVfs                 ,


-- ** getVf #method:getVf#

#if defined(ENABLE_OVERLOADING)
    SettingSriovGetVfMethodInfo             ,
#endif
    settingSriovGetVf                       ,


-- ** new #method:new#

    settingSriovNew                         ,


-- ** removeVf #method:removeVf#

#if defined(ENABLE_OVERLOADING)
    SettingSriovRemoveVfMethodInfo          ,
#endif
    settingSriovRemoveVf                    ,


-- ** removeVfByIndex #method:removeVfByIndex#

#if defined(ENABLE_OVERLOADING)
    SettingSriovRemoveVfByIndexMethodInfo   ,
#endif
    settingSriovRemoveVfByIndex             ,




 -- * Properties


-- ** autoprobeDrivers #attr:autoprobeDrivers#
-- | Whether to autoprobe virtual functions by a compatible driver.
-- 
-- If set to 'GI.NM.Enums.TernaryTrue', the kernel will try to bind VFs to
-- a compatible driver and if this succeeds a new network
-- interface will be instantiated for each VF.
-- 
-- If set to 'GI.NM.Enums.TernaryFalse', VFs will not be claimed and no
-- network interfaces will be created for them.
-- 
-- When set to 'GI.NM.Enums.TernaryDefault', the global default is used; in
-- case the global default is unspecified it is assumed to be
-- 'GI.NM.Enums.TernaryTrue'.
-- 
-- /Since: 1.14/

#if defined(ENABLE_OVERLOADING)
    SettingSriovAutoprobeDriversPropertyInfo,
#endif
    constructSettingSriovAutoprobeDrivers   ,
    getSettingSriovAutoprobeDrivers         ,
    setSettingSriovAutoprobeDrivers         ,
#if defined(ENABLE_OVERLOADING)
    settingSriovAutoprobeDrivers            ,
#endif


-- ** eswitchEncapMode #attr:eswitchEncapMode#
-- | Select the eswitch encapsulation support.
-- 
-- Currently it\'s only supported for PCI PF devices, and only if the eswitch device
-- is managed from the same PCI address than the PF.
-- 
-- If set to 'GI.NM.Enums.SriovEswitchEncapModePreserve' (default) the eswitch encap-mode
-- won\'t be modified by NetworkManager.
-- 
-- /Since: 1.46/

#if defined(ENABLE_OVERLOADING)
    SettingSriovEswitchEncapModePropertyInfo,
#endif
    constructSettingSriovEswitchEncapMode   ,
    getSettingSriovEswitchEncapMode         ,
    setSettingSriovEswitchEncapMode         ,
#if defined(ENABLE_OVERLOADING)
    settingSriovEswitchEncapMode            ,
#endif


-- ** eswitchInlineMode #attr:eswitchInlineMode#
-- | Select the eswitch inline-mode of the device. Some HWs need the VF driver to put
-- part of the packet headers on the TX descriptor so the e-switch can do proper
-- matching and steering.
-- 
-- Currently it\'s only supported for PCI PF devices, and only if the eswitch device
-- is managed from the same PCI address than the PF.
-- 
-- If set to 'GI.NM.Enums.SriovEswitchInlineModePreserve' (default) the eswitch inline-mode
-- won\'t be modified by NetworkManager.
-- 
-- /Since: 1.46/

#if defined(ENABLE_OVERLOADING)
    SettingSriovEswitchInlineModePropertyInfo,
#endif
    constructSettingSriovEswitchInlineMode  ,
    getSettingSriovEswitchInlineMode        ,
    setSettingSriovEswitchInlineMode        ,
#if defined(ENABLE_OVERLOADING)
    settingSriovEswitchInlineMode           ,
#endif


-- ** eswitchMode #attr:eswitchMode#
-- | Select the eswitch mode of the device. Currently it\'s only supported for
-- PCI PF devices, and only if the eswitch device is managed from the same
-- PCI address than the PF.
-- 
-- If set to 'GI.NM.Enums.SriovEswitchModePreserve' (default) the eswitch mode won\'t be
-- modified by NetworkManager.
-- 
-- /Since: 1.46/

#if defined(ENABLE_OVERLOADING)
    SettingSriovEswitchModePropertyInfo     ,
#endif
    constructSettingSriovEswitchMode        ,
    getSettingSriovEswitchMode              ,
    setSettingSriovEswitchMode              ,
#if defined(ENABLE_OVERLOADING)
    settingSriovEswitchMode                 ,
#endif


-- ** totalVfs #attr:totalVfs#
-- | The total number of virtual functions to create.
-- 
-- Note that when the sriov setting is present NetworkManager
-- enforces the number of virtual functions on the interface
-- (also when it is zero) during activation and resets it
-- upon deactivation. To prevent any changes to SR-IOV
-- parameters don\'t add a sriov setting to the connection.
-- 
-- /Since: 1.14/

#if defined(ENABLE_OVERLOADING)
    SettingSriovTotalVfsPropertyInfo        ,
#endif
    constructSettingSriovTotalVfs           ,
    getSettingSriovTotalVfs                 ,
    setSettingSriovTotalVfs                 ,
#if defined(ENABLE_OVERLOADING)
    settingSriovTotalVfs                    ,
#endif


-- ** vfs #attr:vfs#

#if defined(ENABLE_OVERLOADING)
    SettingSriovVfsPropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    settingSriovVfs                         ,
#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.SriovVF as NM.SriovVF
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec

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

#endif

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

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

foreign import ccall "nm_setting_sriov_get_type"
    c_nm_setting_sriov_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingSriov where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_sriov_get_type

instance B.Types.GObject SettingSriov

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSettingSriovMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSettingSriovMethod "addVf" o = SettingSriovAddVfMethodInfo
    ResolveSettingSriovMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSettingSriovMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSettingSriovMethod "clearVfs" o = SettingSriovClearVfsMethodInfo
    ResolveSettingSriovMethod "compare" o = NM.Setting.SettingCompareMethodInfo
    ResolveSettingSriovMethod "diff" o = NM.Setting.SettingDiffMethodInfo
    ResolveSettingSriovMethod "duplicate" o = NM.Setting.SettingDuplicateMethodInfo
    ResolveSettingSriovMethod "enumerateValues" o = NM.Setting.SettingEnumerateValuesMethodInfo
    ResolveSettingSriovMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSettingSriovMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSettingSriovMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSettingSriovMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSettingSriovMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSettingSriovMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSettingSriovMethod "optionClearByName" o = NM.Setting.SettingOptionClearByNameMethodInfo
    ResolveSettingSriovMethod "optionGet" o = NM.Setting.SettingOptionGetMethodInfo
    ResolveSettingSriovMethod "optionGetAllNames" o = NM.Setting.SettingOptionGetAllNamesMethodInfo
    ResolveSettingSriovMethod "optionGetBoolean" o = NM.Setting.SettingOptionGetBooleanMethodInfo
    ResolveSettingSriovMethod "optionGetUint32" o = NM.Setting.SettingOptionGetUint32MethodInfo
    ResolveSettingSriovMethod "optionSet" o = NM.Setting.SettingOptionSetMethodInfo
    ResolveSettingSriovMethod "optionSetBoolean" o = NM.Setting.SettingOptionSetBooleanMethodInfo
    ResolveSettingSriovMethod "optionSetUint32" o = NM.Setting.SettingOptionSetUint32MethodInfo
    ResolveSettingSriovMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSettingSriovMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSettingSriovMethod "removeVf" o = SettingSriovRemoveVfMethodInfo
    ResolveSettingSriovMethod "removeVfByIndex" o = SettingSriovRemoveVfByIndexMethodInfo
    ResolveSettingSriovMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSettingSriovMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSettingSriovMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSettingSriovMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSettingSriovMethod "toString" o = NM.Setting.SettingToStringMethodInfo
    ResolveSettingSriovMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSettingSriovMethod "verify" o = NM.Setting.SettingVerifyMethodInfo
    ResolveSettingSriovMethod "verifySecrets" o = NM.Setting.SettingVerifySecretsMethodInfo
    ResolveSettingSriovMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSettingSriovMethod "getAutoprobeDrivers" o = SettingSriovGetAutoprobeDriversMethodInfo
    ResolveSettingSriovMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSettingSriovMethod "getDbusPropertyType" o = NM.Setting.SettingGetDbusPropertyTypeMethodInfo
    ResolveSettingSriovMethod "getEswitchEncapMode" o = SettingSriovGetEswitchEncapModeMethodInfo
    ResolveSettingSriovMethod "getEswitchInlineMode" o = SettingSriovGetEswitchInlineModeMethodInfo
    ResolveSettingSriovMethod "getEswitchMode" o = SettingSriovGetEswitchModeMethodInfo
    ResolveSettingSriovMethod "getName" o = NM.Setting.SettingGetNameMethodInfo
    ResolveSettingSriovMethod "getNumVfs" o = SettingSriovGetNumVfsMethodInfo
    ResolveSettingSriovMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingSriovMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingSriovMethod "getSecretFlags" o = NM.Setting.SettingGetSecretFlagsMethodInfo
    ResolveSettingSriovMethod "getTotalVfs" o = SettingSriovGetTotalVfsMethodInfo
    ResolveSettingSriovMethod "getVf" o = SettingSriovGetVfMethodInfo
    ResolveSettingSriovMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingSriovMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingSriovMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingSriovMethod "setSecretFlags" o = NM.Setting.SettingSetSecretFlagsMethodInfo
    ResolveSettingSriovMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

-- | Get the value of the “@autoprobe-drivers@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingSriov #autoprobeDrivers
-- @
getSettingSriovAutoprobeDrivers :: (MonadIO m, IsSettingSriov o) => o -> m NM.Enums.Ternary
getSettingSriovAutoprobeDrivers :: forall (m :: * -> *) o.
(MonadIO m, IsSettingSriov o) =>
o -> m Ternary
getSettingSriovAutoprobeDrivers 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
"autoprobe-drivers"

-- | Set the value of the “@autoprobe-drivers@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingSriov [ #autoprobeDrivers 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingSriovAutoprobeDrivers :: (MonadIO m, IsSettingSriov o) => o -> NM.Enums.Ternary -> m ()
setSettingSriovAutoprobeDrivers :: forall (m :: * -> *) o.
(MonadIO m, IsSettingSriov o) =>
o -> Ternary -> m ()
setSettingSriovAutoprobeDrivers 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
"autoprobe-drivers" Ternary
val

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

#if defined(ENABLE_OVERLOADING)
data SettingSriovAutoprobeDriversPropertyInfo
instance AttrInfo SettingSriovAutoprobeDriversPropertyInfo where
    type AttrAllowedOps SettingSriovAutoprobeDriversPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingSriovAutoprobeDriversPropertyInfo = IsSettingSriov
    type AttrSetTypeConstraint SettingSriovAutoprobeDriversPropertyInfo = (~) NM.Enums.Ternary
    type AttrTransferTypeConstraint SettingSriovAutoprobeDriversPropertyInfo = (~) NM.Enums.Ternary
    type AttrTransferType SettingSriovAutoprobeDriversPropertyInfo = NM.Enums.Ternary
    type AttrGetType SettingSriovAutoprobeDriversPropertyInfo = NM.Enums.Ternary
    type AttrLabel SettingSriovAutoprobeDriversPropertyInfo = "autoprobe-drivers"
    type AttrOrigin SettingSriovAutoprobeDriversPropertyInfo = SettingSriov
    attrGet = getSettingSriovAutoprobeDrivers
    attrSet = setSettingSriovAutoprobeDrivers
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingSriovAutoprobeDrivers
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingSriov.autoprobeDrivers"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingSriov.html#g:attr:autoprobeDrivers"
        })
#endif

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

-- | Get the value of the “@eswitch-encap-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingSriov #eswitchEncapMode
-- @
getSettingSriovEswitchEncapMode :: (MonadIO m, IsSettingSriov o) => o -> m Int32
getSettingSriovEswitchEncapMode :: forall (m :: * -> *) o.
(MonadIO m, IsSettingSriov o) =>
o -> m Int32
getSettingSriovEswitchEncapMode o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"eswitch-encap-mode"

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

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

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

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

-- | Get the value of the “@eswitch-inline-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingSriov #eswitchInlineMode
-- @
getSettingSriovEswitchInlineMode :: (MonadIO m, IsSettingSriov o) => o -> m Int32
getSettingSriovEswitchInlineMode :: forall (m :: * -> *) o.
(MonadIO m, IsSettingSriov o) =>
o -> m Int32
getSettingSriovEswitchInlineMode o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"eswitch-inline-mode"

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

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

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

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

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

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

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

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

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

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

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

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

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

-- XXX Generation of property "vfs" of object "SettingSriov" failed.
-- Not implemented: Don't know how to handle properties of type TPtrArray (TInterface (Name {namespace = "NM", name = "SriovVF"}))
#if defined(ENABLE_OVERLOADING)
-- XXX Placeholder
data SettingSriovVfsPropertyInfo
instance AttrInfo SettingSriovVfsPropertyInfo where
    type AttrAllowedOps SettingSriovVfsPropertyInfo = '[]
    type AttrSetTypeConstraint SettingSriovVfsPropertyInfo = (~) ()
    type AttrTransferTypeConstraint SettingSriovVfsPropertyInfo = (~) ()
    type AttrTransferType SettingSriovVfsPropertyInfo = ()
    type AttrBaseTypeConstraint SettingSriovVfsPropertyInfo = (~) ()
    type AttrGetType SettingSriovVfsPropertyInfo = ()
    type AttrLabel SettingSriovVfsPropertyInfo = ""
    type AttrOrigin SettingSriovVfsPropertyInfo = SettingSriov
    attrGet = undefined
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingSriov
type instance O.AttributeList SettingSriov = SettingSriovAttributeList
type SettingSriovAttributeList = ('[ '("autoprobeDrivers", SettingSriovAutoprobeDriversPropertyInfo), '("eswitchEncapMode", SettingSriovEswitchEncapModePropertyInfo), '("eswitchInlineMode", SettingSriovEswitchInlineModePropertyInfo), '("eswitchMode", SettingSriovEswitchModePropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("totalVfs", SettingSriovTotalVfsPropertyInfo), '("vfs", SettingSriovVfsPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingSriovAutoprobeDrivers :: AttrLabelProxy "autoprobeDrivers"
settingSriovAutoprobeDrivers = AttrLabelProxy

settingSriovEswitchEncapMode :: AttrLabelProxy "eswitchEncapMode"
settingSriovEswitchEncapMode = AttrLabelProxy

settingSriovEswitchInlineMode :: AttrLabelProxy "eswitchInlineMode"
settingSriovEswitchInlineMode = AttrLabelProxy

settingSriovEswitchMode :: AttrLabelProxy "eswitchMode"
settingSriovEswitchMode = AttrLabelProxy

settingSriovTotalVfs :: AttrLabelProxy "totalVfs"
settingSriovTotalVfs = AttrLabelProxy

settingSriovVfs :: AttrLabelProxy "vfs"
settingSriovVfs = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "nm_setting_sriov_new" nm_setting_sriov_new :: 
    IO (Ptr SettingSriov)

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

#if defined(ENABLE_OVERLOADING)
#endif

-- method SettingSriov::add_vf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingSriov" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingSriov"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "vf"
--           , argType = TInterface Name { namespace = "NM" , name = "SriovVF" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the VF to add" , 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_sriov_add_vf" nm_setting_sriov_add_vf :: 
    Ptr SettingSriov ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingSriov"})
    Ptr NM.SriovVF.SriovVF ->               -- vf : TInterface (Name {namespace = "NM", name = "SriovVF"})
    IO ()

-- | Appends a new VF and associated information to the setting.  The
-- given VF is duplicated internally and is not changed by this function.
-- 
-- /Since: 1.14/
settingSriovAddVf ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> NM.SriovVF.SriovVF
    -- ^ /@vf@/: the VF to add
    -> m ()
settingSriovAddVf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> SriovVF -> m ()
settingSriovAddVf a
setting SriovVF
vf = 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 SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Ptr SriovVF
vf' <- SriovVF -> IO (Ptr SriovVF)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SriovVF
vf
    Ptr SettingSriov -> Ptr SriovVF -> IO ()
nm_setting_sriov_add_vf Ptr SettingSriov
setting' Ptr SriovVF
vf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    SriovVF -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SriovVF
vf
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingSriovAddVfMethodInfo
instance (signature ~ (NM.SriovVF.SriovVF -> m ()), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovAddVfMethodInfo a signature where
    overloadedMethod = settingSriovAddVf

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


#endif

-- method SettingSriov::clear_vfs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingSriov" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingSriov"
--                 , 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_sriov_clear_vfs" nm_setting_sriov_clear_vfs :: 
    Ptr SettingSriov ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingSriov"})
    IO ()

-- | Removes all configured VFs.
-- 
-- /Since: 1.14/
settingSriovClearVfs ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> m ()
settingSriovClearVfs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> m ()
settingSriovClearVfs a
setting = 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 SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Ptr SettingSriov -> IO ()
nm_setting_sriov_clear_vfs Ptr SettingSriov
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingSriovClearVfsMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovClearVfsMethodInfo a signature where
    overloadedMethod = settingSriovClearVfs

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


#endif

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

-- | Returns the value contained in the [SettingSriov:autoprobeDrivers]("GI.NM.Objects.SettingSriov#g:attr:autoprobeDrivers")
-- property.
-- 
-- /Since: 1.14/
settingSriovGetAutoprobeDrivers ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> m NM.Enums.Ternary
    -- ^ __Returns:__ the autoprobe-drivers property value
settingSriovGetAutoprobeDrivers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> m Ternary
settingSriovGetAutoprobeDrivers a
setting = 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 SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingSriov -> IO CInt
nm_setting_sriov_get_autoprobe_drivers Ptr SettingSriov
setting'
    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
setting
    Ternary -> IO Ternary
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ternary
result'

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

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


#endif

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

foreign import ccall "nm_setting_sriov_get_eswitch_encap_mode" nm_setting_sriov_get_eswitch_encap_mode :: 
    Ptr SettingSriov ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingSriov"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.46/
settingSriovGetEswitchEncapMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> m NM.Enums.SriovEswitchEncapMode
    -- ^ __Returns:__ the value contained in the [SettingSriov:eswitchEncapMode]("GI.NM.Objects.SettingSriov#g:attr:eswitchEncapMode") property.
settingSriovGetEswitchEncapMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> m SriovEswitchEncapMode
settingSriovGetEswitchEncapMode a
setting = IO SriovEswitchEncapMode -> m SriovEswitchEncapMode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SriovEswitchEncapMode -> m SriovEswitchEncapMode)
-> IO SriovEswitchEncapMode -> m SriovEswitchEncapMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingSriov -> IO CInt
nm_setting_sriov_get_eswitch_encap_mode Ptr SettingSriov
setting'
    let result' :: SriovEswitchEncapMode
result' = (Int -> SriovEswitchEncapMode
forall a. Enum a => Int -> a
toEnum (Int -> SriovEswitchEncapMode)
-> (CInt -> Int) -> CInt -> SriovEswitchEncapMode
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
setting
    SriovEswitchEncapMode -> IO SriovEswitchEncapMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SriovEswitchEncapMode
result'

#if defined(ENABLE_OVERLOADING)
data SettingSriovGetEswitchEncapModeMethodInfo
instance (signature ~ (m NM.Enums.SriovEswitchEncapMode), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovGetEswitchEncapModeMethodInfo a signature where
    overloadedMethod = settingSriovGetEswitchEncapMode

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


#endif

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

foreign import ccall "nm_setting_sriov_get_eswitch_inline_mode" nm_setting_sriov_get_eswitch_inline_mode :: 
    Ptr SettingSriov ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingSriov"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.46/
settingSriovGetEswitchInlineMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> m NM.Enums.SriovEswitchInlineMode
    -- ^ __Returns:__ the value contained in the [SettingSriov:eswitchInlineMode]("GI.NM.Objects.SettingSriov#g:attr:eswitchInlineMode") property.
settingSriovGetEswitchInlineMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> m SriovEswitchInlineMode
settingSriovGetEswitchInlineMode a
setting = IO SriovEswitchInlineMode -> m SriovEswitchInlineMode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SriovEswitchInlineMode -> m SriovEswitchInlineMode)
-> IO SriovEswitchInlineMode -> m SriovEswitchInlineMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingSriov -> IO CInt
nm_setting_sriov_get_eswitch_inline_mode Ptr SettingSriov
setting'
    let result' :: SriovEswitchInlineMode
result' = (Int -> SriovEswitchInlineMode
forall a. Enum a => Int -> a
toEnum (Int -> SriovEswitchInlineMode)
-> (CInt -> Int) -> CInt -> SriovEswitchInlineMode
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
setting
    SriovEswitchInlineMode -> IO SriovEswitchInlineMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SriovEswitchInlineMode
result'

#if defined(ENABLE_OVERLOADING)
data SettingSriovGetEswitchInlineModeMethodInfo
instance (signature ~ (m NM.Enums.SriovEswitchInlineMode), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovGetEswitchInlineModeMethodInfo a signature where
    overloadedMethod = settingSriovGetEswitchInlineMode

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


#endif

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

foreign import ccall "nm_setting_sriov_get_eswitch_mode" nm_setting_sriov_get_eswitch_mode :: 
    Ptr SettingSriov ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingSriov"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.46/
settingSriovGetEswitchMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> m NM.Enums.SriovEswitchMode
    -- ^ __Returns:__ the value contained in the [SettingSriov:eswitchMode]("GI.NM.Objects.SettingSriov#g:attr:eswitchMode") property.
settingSriovGetEswitchMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> m SriovEswitchMode
settingSriovGetEswitchMode a
setting = IO SriovEswitchMode -> m SriovEswitchMode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SriovEswitchMode -> m SriovEswitchMode)
-> IO SriovEswitchMode -> m SriovEswitchMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingSriov -> IO CInt
nm_setting_sriov_get_eswitch_mode Ptr SettingSriov
setting'
    let result' :: SriovEswitchMode
result' = (Int -> SriovEswitchMode
forall a. Enum a => Int -> a
toEnum (Int -> SriovEswitchMode)
-> (CInt -> Int) -> CInt -> SriovEswitchMode
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
setting
    SriovEswitchMode -> IO SriovEswitchMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SriovEswitchMode
result'

#if defined(ENABLE_OVERLOADING)
data SettingSriovGetEswitchModeMethodInfo
instance (signature ~ (m NM.Enums.SriovEswitchMode), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovGetEswitchModeMethodInfo a signature where
    overloadedMethod = settingSriovGetEswitchMode

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.14/
settingSriovGetNumVfs ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> m Word32
    -- ^ __Returns:__ the number of configured VFs
settingSriovGetNumVfs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> m Word32
settingSriovGetNumVfs a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingSriov -> IO Word32
nm_setting_sriov_get_num_vfs Ptr SettingSriov
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingSriovGetNumVfsMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovGetNumVfsMethodInfo a signature where
    overloadedMethod = settingSriovGetNumVfs

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


#endif

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

-- | Returns the value contained in the [SettingSriov:totalVfs]("GI.NM.Objects.SettingSriov#g:attr:totalVfs")
-- property.
-- 
-- /Since: 1.14/
settingSriovGetTotalVfs ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> m Word32
    -- ^ __Returns:__ the total number of SR-IOV virtual functions to create
settingSriovGetTotalVfs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> m Word32
settingSriovGetTotalVfs a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Word32
result <- Ptr SettingSriov -> IO Word32
nm_setting_sriov_get_total_vfs Ptr SettingSriov
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data SettingSriovGetTotalVfsMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovGetTotalVfsMethodInfo a signature where
    overloadedMethod = settingSriovGetTotalVfs

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


#endif

-- method SettingSriov::get_vf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingSriov" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingSriov"
--                 , 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 "index number of the VF to return"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "NM" , name = "SriovVF" })
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_sriov_get_vf" nm_setting_sriov_get_vf :: 
    Ptr SettingSriov ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingSriov"})
    Word32 ->                               -- idx : TBasicType TUInt
    IO (Ptr NM.SriovVF.SriovVF)

-- | /No description available in the introspection data./
-- 
-- /Since: 1.14/
settingSriovGetVf ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> Word32
    -- ^ /@idx@/: index number of the VF to return
    -> m NM.SriovVF.SriovVF
    -- ^ __Returns:__ the VF at index /@idx@/
settingSriovGetVf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> Word32 -> m SriovVF
settingSriovGetVf a
setting Word32
idx = IO SriovVF -> m SriovVF
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SriovVF -> m SriovVF) -> IO SriovVF -> m SriovVF
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Ptr SriovVF
result <- Ptr SettingSriov -> Word32 -> IO (Ptr SriovVF)
nm_setting_sriov_get_vf Ptr SettingSriov
setting' Word32
idx
    Text -> Ptr SriovVF -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingSriovGetVf" Ptr SriovVF
result
    SriovVF
result' <- ((ManagedPtr SriovVF -> SriovVF) -> Ptr SriovVF -> IO SriovVF
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr SriovVF -> SriovVF
NM.SriovVF.SriovVF) Ptr SriovVF
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    SriovVF -> IO SriovVF
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SriovVF
result'

#if defined(ENABLE_OVERLOADING)
data SettingSriovGetVfMethodInfo
instance (signature ~ (Word32 -> m NM.SriovVF.SriovVF), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovGetVfMethodInfo a signature where
    overloadedMethod = settingSriovGetVf

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


#endif

-- method SettingSriov::remove_vf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingSriov" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingSriov"
--                 , 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 "index number of the VF"
--                 , 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_sriov_remove_vf" nm_setting_sriov_remove_vf :: 
    Ptr SettingSriov ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingSriov"})
    Word32 ->                               -- idx : TBasicType TUInt
    IO ()

-- | Removes the VF at index /@idx@/.
-- 
-- /Since: 1.14/
settingSriovRemoveVf ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> Word32
    -- ^ /@idx@/: index number of the VF
    -> m ()
settingSriovRemoveVf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> Word32 -> m ()
settingSriovRemoveVf a
setting 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 SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    Ptr SettingSriov -> Word32 -> IO ()
nm_setting_sriov_remove_vf Ptr SettingSriov
setting' Word32
idx
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingSriovRemoveVfMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSettingSriov a) => O.OverloadedMethod SettingSriovRemoveVfMethodInfo a signature where
    overloadedMethod = settingSriovRemoveVf

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


#endif

-- method SettingSriov::remove_vf_by_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingSriov" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingSriov"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the VF index of the VF 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_sriov_remove_vf_by_index" nm_setting_sriov_remove_vf_by_index :: 
    Ptr SettingSriov ->                     -- setting : TInterface (Name {namespace = "NM", name = "SettingSriov"})
    Word32 ->                               -- index : TBasicType TUInt
    IO CInt

-- | Removes the VF with VF index /@index@/.
-- 
-- /Since: 1.14/
settingSriovRemoveVfByIndex ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingSriov a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingSriov.SettingSriov'
    -> Word32
    -- ^ /@index@/: the VF index of the VF to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the VF was found and removed; 'P.False' if it was not
settingSriovRemoveVfByIndex :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingSriov a) =>
a -> Word32 -> m Bool
settingSriovRemoveVfByIndex a
setting Word32
index = 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 SettingSriov
setting' <- a -> IO (Ptr SettingSriov)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingSriov -> Word32 -> IO CInt
nm_setting_sriov_remove_vf_by_index Ptr SettingSriov
setting' Word32
index
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

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

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


#endif