{-# LANGUAGE TypeApplications #-}


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

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

module GI.NM.Objects.SettingMacvlan
    ( 

-- * Exported types
    SettingMacvlan(..)                      ,
    IsSettingMacvlan                        ,
    toSettingMacvlan                        ,


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

-- ** getMode #method:getMode#

#if defined(ENABLE_OVERLOADING)
    SettingMacvlanGetModeMethodInfo         ,
#endif
    settingMacvlanGetMode                   ,


-- ** getParent #method:getParent#

#if defined(ENABLE_OVERLOADING)
    SettingMacvlanGetParentMethodInfo       ,
#endif
    settingMacvlanGetParent                 ,


-- ** getPromiscuous #method:getPromiscuous#

#if defined(ENABLE_OVERLOADING)
    SettingMacvlanGetPromiscuousMethodInfo  ,
#endif
    settingMacvlanGetPromiscuous            ,


-- ** getTap #method:getTap#

#if defined(ENABLE_OVERLOADING)
    SettingMacvlanGetTapMethodInfo          ,
#endif
    settingMacvlanGetTap                    ,


-- ** new #method:new#

    settingMacvlanNew                       ,




 -- * Properties


-- ** mode #attr:mode#
-- | The macvlan mode, which specifies the communication mechanism between multiple
-- macvlans on the same lower device.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingMacvlanModePropertyInfo          ,
#endif
    constructSettingMacvlanMode             ,
    getSettingMacvlanMode                   ,
    setSettingMacvlanMode                   ,
#if defined(ENABLE_OVERLOADING)
    settingMacvlanMode                      ,
#endif


-- ** parent #attr:parent#
-- | If given, specifies the parent interface name or parent connection UUID
-- from which this MAC-VLAN interface should be created.  If this property is
-- not specified, the connection must contain an t'GI.NM.Objects.SettingWired.SettingWired' setting
-- with a [SettingWired:macAddress]("GI.NM.Objects.SettingWired#g:attr:macAddress") property.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingMacvlanParentPropertyInfo        ,
#endif
    clearSettingMacvlanParent               ,
    constructSettingMacvlanParent           ,
    getSettingMacvlanParent                 ,
    setSettingMacvlanParent                 ,
#if defined(ENABLE_OVERLOADING)
    settingMacvlanParent                    ,
#endif


-- ** promiscuous #attr:promiscuous#
-- | Whether the interface should be put in promiscuous mode.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    SettingMacvlanPromiscuousPropertyInfo   ,
#endif
    constructSettingMacvlanPromiscuous      ,
    getSettingMacvlanPromiscuous            ,
    setSettingMacvlanPromiscuous            ,
#if defined(ENABLE_OVERLOADING)
    settingMacvlanPromiscuous               ,
#endif


-- ** tap #attr:tap#
-- | Whether the interface should be a MACVTAP.
-- 
-- /Since: 1.2/

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

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

#endif

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

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

foreign import ccall "nm_setting_macvlan_get_type"
    c_nm_setting_macvlan_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingMacvlan where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_macvlan_get_type

instance B.Types.GObject SettingMacvlan

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

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

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

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

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

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

#endif

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

#endif

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

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

-- | Set the value of the “@mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingMacvlan [ #mode 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingMacvlanMode :: (MonadIO m, IsSettingMacvlan o) => o -> Word32 -> m ()
setSettingMacvlanMode :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMacvlan o) =>
o -> Word32 -> m ()
setSettingMacvlanMode o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"mode" Word32
val

-- | Construct a t'GValueConstruct' with valid value for the “@mode@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingMacvlanMode :: (IsSettingMacvlan o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingMacvlanMode :: forall o (m :: * -> *).
(IsSettingMacvlan o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingMacvlanMode Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"mode" Word32
val

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

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

-- | Get the value of the “@parent@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settingMacvlan #parent
-- @
getSettingMacvlanParent :: (MonadIO m, IsSettingMacvlan o) => o -> m T.Text
getSettingMacvlanParent :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMacvlan o) =>
o -> m Text
getSettingMacvlanParent 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
"getSettingMacvlanParent" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"parent"

-- | Set the value of the “@parent@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingMacvlan [ #parent 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingMacvlanParent :: (MonadIO m, IsSettingMacvlan o) => o -> T.Text -> m ()
setSettingMacvlanParent :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMacvlan o) =>
o -> Text -> m ()
setSettingMacvlanParent o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"parent" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a t'GValueConstruct' with valid value for the “@parent@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingMacvlanParent :: (IsSettingMacvlan o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingMacvlanParent :: forall o (m :: * -> *).
(IsSettingMacvlan o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingMacvlanParent Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"parent" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@parent@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #parent
-- @
clearSettingMacvlanParent :: (MonadIO m, IsSettingMacvlan o) => o -> m ()
clearSettingMacvlanParent :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMacvlan o) =>
o -> m ()
clearSettingMacvlanParent o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"parent" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

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

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

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

-- | Set the value of the “@promiscuous@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingMacvlan [ #promiscuous 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingMacvlanPromiscuous :: (MonadIO m, IsSettingMacvlan o) => o -> Bool -> m ()
setSettingMacvlanPromiscuous :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMacvlan o) =>
o -> Bool -> m ()
setSettingMacvlanPromiscuous o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"promiscuous" Bool
val

-- | Construct a t'GValueConstruct' with valid value for the “@promiscuous@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingMacvlanPromiscuous :: (IsSettingMacvlan o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSettingMacvlanPromiscuous :: forall o (m :: * -> *).
(IsSettingMacvlan o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSettingMacvlanPromiscuous Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"promiscuous" Bool
val

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

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

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

-- | Set the value of the “@tap@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingMacvlan [ #tap 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingMacvlanTap :: (MonadIO m, IsSettingMacvlan o) => o -> Bool -> m ()
setSettingMacvlanTap :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMacvlan o) =>
o -> Bool -> m ()
setSettingMacvlanTap o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"tap" Bool
val

-- | Construct a t'GValueConstruct' with valid value for the “@tap@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingMacvlanTap :: (IsSettingMacvlan o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSettingMacvlanTap :: forall o (m :: * -> *).
(IsSettingMacvlan o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSettingMacvlanTap Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"tap" Bool
val

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingMacvlan
type instance O.AttributeList SettingMacvlan = SettingMacvlanAttributeList
type SettingMacvlanAttributeList = ('[ '("mode", SettingMacvlanModePropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("parent", SettingMacvlanParentPropertyInfo), '("promiscuous", SettingMacvlanPromiscuousPropertyInfo), '("tap", SettingMacvlanTapPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingMacvlanMode :: AttrLabelProxy "mode"
settingMacvlanMode = AttrLabelProxy

settingMacvlanParent :: AttrLabelProxy "parent"
settingMacvlanParent = AttrLabelProxy

settingMacvlanPromiscuous :: AttrLabelProxy "promiscuous"
settingMacvlanPromiscuous = AttrLabelProxy

settingMacvlanTap :: AttrLabelProxy "tap"
settingMacvlanTap = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "nm_setting_macvlan_new" nm_setting_macvlan_new :: 
    IO (Ptr SettingMacvlan)

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

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingMacvlanGetMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingMacvlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingMacvlan.SettingMacvlan'
    -> m NM.Enums.SettingMacvlanMode
    -- ^ __Returns:__ the [SettingMacvlan:mode]("GI.NM.Objects.SettingMacvlan#g:attr:mode") property of the setting
settingMacvlanGetMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMacvlan a) =>
a -> m SettingMacvlanMode
settingMacvlanGetMode a
setting = IO SettingMacvlanMode -> m SettingMacvlanMode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingMacvlanMode -> m SettingMacvlanMode)
-> IO SettingMacvlanMode -> m SettingMacvlanMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingMacvlan
setting' <- a -> IO (Ptr SettingMacvlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CUInt
result <- Ptr SettingMacvlan -> IO CUInt
nm_setting_macvlan_get_mode Ptr SettingMacvlan
setting'
    let result' :: SettingMacvlanMode
result' = (Int -> SettingMacvlanMode
forall a. Enum a => Int -> a
toEnum (Int -> SettingMacvlanMode)
-> (CUInt -> Int) -> CUInt -> SettingMacvlanMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    SettingMacvlanMode -> IO SettingMacvlanMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SettingMacvlanMode
result'

#if defined(ENABLE_OVERLOADING)
data SettingMacvlanGetModeMethodInfo
instance (signature ~ (m NM.Enums.SettingMacvlanMode), MonadIO m, IsSettingMacvlan a) => O.OverloadedMethod SettingMacvlanGetModeMethodInfo a signature where
    overloadedMethod = settingMacvlanGetMode

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


#endif

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

foreign import ccall "nm_setting_macvlan_get_parent" nm_setting_macvlan_get_parent :: 
    Ptr SettingMacvlan ->                   -- setting : TInterface (Name {namespace = "NM", name = "SettingMacvlan"})
    IO CString

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingMacvlanGetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingMacvlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingMacvlan.SettingMacvlan'
    -> m T.Text
    -- ^ __Returns:__ the [SettingMacvlan:parent]("GI.NM.Objects.SettingMacvlan#g:attr:parent") property of the setting
settingMacvlanGetParent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMacvlan a) =>
a -> m Text
settingMacvlanGetParent a
setting = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingMacvlan
setting' <- a -> IO (Ptr SettingMacvlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingMacvlan -> IO CString
nm_setting_macvlan_get_parent Ptr SettingMacvlan
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMacvlanGetParent" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SettingMacvlanGetParentMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingMacvlan a) => O.OverloadedMethod SettingMacvlanGetParentMethodInfo a signature where
    overloadedMethod = settingMacvlanGetParent

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingMacvlanGetPromiscuous ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingMacvlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingMacvlan.SettingMacvlan'
    -> m Bool
    -- ^ __Returns:__ the [SettingMacvlan:promiscuous]("GI.NM.Objects.SettingMacvlan#g:attr:promiscuous") property of the setting
settingMacvlanGetPromiscuous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMacvlan a) =>
a -> m Bool
settingMacvlanGetPromiscuous a
setting = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingMacvlan
setting' <- a -> IO (Ptr SettingMacvlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingMacvlan -> IO CInt
nm_setting_macvlan_get_promiscuous Ptr SettingMacvlan
setting'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingMacvlanGetPromiscuousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingMacvlan a) => O.OverloadedMethod SettingMacvlanGetPromiscuousMethodInfo a signature where
    overloadedMethod = settingMacvlanGetPromiscuous

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


#endif

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

-- | /No description available in the introspection data./
-- 
-- /Since: 1.2/
settingMacvlanGetTap ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingMacvlan a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingMacvlan.SettingMacvlan'
    -> m Bool
    -- ^ __Returns:__ the [SettingMacvlan:tap]("GI.NM.Objects.SettingMacvlan#g:attr:tap") property of the setting
settingMacvlanGetTap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMacvlan a) =>
a -> m Bool
settingMacvlanGetTap a
setting = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingMacvlan
setting' <- a -> IO (Ptr SettingMacvlan)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CInt
result <- Ptr SettingMacvlan -> IO CInt
nm_setting_macvlan_get_tap Ptr SettingMacvlan
setting'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SettingMacvlanGetTapMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSettingMacvlan a) => O.OverloadedMethod SettingMacvlanGetTapMethodInfo a signature where
    overloadedMethod = settingMacvlanGetTap

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


#endif