{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.NM.Objects.DeviceHsr
(
DeviceHsr(..) ,
IsDeviceHsr ,
toDeviceHsr ,
#if defined(ENABLE_OVERLOADING)
ResolveDeviceHsrMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceHsrGetMulticastSpecMethodInfo ,
#endif
deviceHsrGetMulticastSpec ,
#if defined(ENABLE_OVERLOADING)
DeviceHsrGetPort1MethodInfo ,
#endif
deviceHsrGetPort1 ,
#if defined(ENABLE_OVERLOADING)
DeviceHsrGetPort2MethodInfo ,
#endif
deviceHsrGetPort2 ,
#if defined(ENABLE_OVERLOADING)
DeviceHsrGetPrpMethodInfo ,
#endif
deviceHsrGetPrp ,
#if defined(ENABLE_OVERLOADING)
DeviceHsrGetSupervisionAddressMethodInfo,
#endif
deviceHsrGetSupervisionAddress ,
#if defined(ENABLE_OVERLOADING)
DeviceHsrMulticastSpecPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceHsrMulticastSpec ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceHsrPort1PropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceHsrPort1 ,
#endif
getDeviceHsrPort1 ,
#if defined(ENABLE_OVERLOADING)
DeviceHsrPort2PropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceHsrPort2 ,
#endif
getDeviceHsrPort2 ,
#if defined(ENABLE_OVERLOADING)
DeviceHsrPrpPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceHsrPrp ,
#endif
getDeviceHsrPrp ,
#if defined(ENABLE_OVERLOADING)
DeviceHsrSupervisionAddressPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceHsrSupervisionAddress ,
#endif
getDeviceHsrSupervisionAddress ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.MainContext as GLib.MainContext
import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncInitable as Gio.AsyncInitable
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.DBusConnection as Gio.DBusConnection
import qualified GI.NM.Callbacks as NM.Callbacks
import {-# SOURCE #-} qualified GI.NM.Enums as NM.Enums
import {-# SOURCE #-} qualified GI.NM.Flags as NM.Flags
import {-# SOURCE #-} qualified GI.NM.Interfaces.Connection as NM.Connection
import {-# SOURCE #-} qualified GI.NM.Objects.ActiveConnection as NM.ActiveConnection
import {-# SOURCE #-} qualified GI.NM.Objects.Checkpoint as NM.Checkpoint
import {-# SOURCE #-} qualified GI.NM.Objects.Client as NM.Client
import {-# SOURCE #-} qualified GI.NM.Objects.Device as NM.Device
import {-# SOURCE #-} qualified GI.NM.Objects.DhcpConfig as NM.DhcpConfig
import {-# SOURCE #-} qualified GI.NM.Objects.IPConfig as NM.IPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.Object as NM.Object
import {-# SOURCE #-} qualified GI.NM.Objects.RemoteConnection as NM.RemoteConnection
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
import {-# SOURCE #-} qualified GI.NM.Objects.Setting8021x as NM.Setting8021x
import {-# SOURCE #-} qualified GI.NM.Objects.SettingAdsl as NM.SettingAdsl
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBluetooth as NM.SettingBluetooth
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBond as NM.SettingBond
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridge as NM.SettingBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridgePort as NM.SettingBridgePort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingCdma as NM.SettingCdma
import {-# SOURCE #-} qualified GI.NM.Objects.SettingConnection as NM.SettingConnection
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDcb as NM.SettingDcb
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDummy as NM.SettingDummy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGeneric as NM.SettingGeneric
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGsm as NM.SettingGsm
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP4Config as NM.SettingIP4Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP6Config as NM.SettingIP6Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPConfig as NM.SettingIPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPTunnel as NM.SettingIPTunnel
import {-# SOURCE #-} qualified GI.NM.Objects.SettingInfiniband as NM.SettingInfiniband
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacsec as NM.SettingMacsec
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacvlan as NM.SettingMacvlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOlpcMesh as NM.SettingOlpcMesh
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsBridge as NM.SettingOvsBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsInterface as NM.SettingOvsInterface
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPatch as NM.SettingOvsPatch
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPort as NM.SettingOvsPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPpp as NM.SettingPpp
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPppoe as NM.SettingPppoe
import {-# SOURCE #-} qualified GI.NM.Objects.SettingProxy as NM.SettingProxy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingSerial as NM.SettingSerial
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTCConfig as NM.SettingTCConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeam as NM.SettingTeam
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeamPort as NM.SettingTeamPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTun as NM.SettingTun
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVlan as NM.SettingVlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVpn as NM.SettingVpn
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVxlan as NM.SettingVxlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWimax as NM.SettingWimax
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWired as NM.SettingWired
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWireless as NM.SettingWireless
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWirelessSecurity as NM.SettingWirelessSecurity
import {-# SOURCE #-} qualified GI.NM.Structs.BridgeVlan as NM.BridgeVlan
import {-# SOURCE #-} qualified GI.NM.Structs.DnsEntry as NM.DnsEntry
import {-# SOURCE #-} qualified GI.NM.Structs.IPAddress as NM.IPAddress
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoute as NM.IPRoute
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoutingRule as NM.IPRoutingRule
import {-# SOURCE #-} qualified GI.NM.Structs.LldpNeighbor as NM.LldpNeighbor
import {-# SOURCE #-} qualified GI.NM.Structs.Range as NM.Range
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.NM.Objects.Device as NM.Device
import {-# SOURCE #-} qualified GI.NM.Objects.Object as NM.Object
#endif
newtype DeviceHsr = DeviceHsr (SP.ManagedPtr DeviceHsr)
deriving (DeviceHsr -> DeviceHsr -> Bool
(DeviceHsr -> DeviceHsr -> Bool)
-> (DeviceHsr -> DeviceHsr -> Bool) -> Eq DeviceHsr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeviceHsr -> DeviceHsr -> Bool
== :: DeviceHsr -> DeviceHsr -> Bool
$c/= :: DeviceHsr -> DeviceHsr -> Bool
/= :: DeviceHsr -> DeviceHsr -> Bool
Eq)
instance SP.ManagedPtrNewtype DeviceHsr where
toManagedPtr :: DeviceHsr -> ManagedPtr DeviceHsr
toManagedPtr (DeviceHsr ManagedPtr DeviceHsr
p) = ManagedPtr DeviceHsr
p
foreign import ccall "nm_device_hsr_get_type"
c_nm_device_hsr_get_type :: IO B.Types.GType
instance B.Types.TypedObject DeviceHsr where
glibType :: IO GType
glibType = IO GType
c_nm_device_hsr_get_type
instance B.Types.GObject DeviceHsr
class (SP.GObject o, O.IsDescendantOf DeviceHsr o) => IsDeviceHsr o
instance (SP.GObject o, O.IsDescendantOf DeviceHsr o) => IsDeviceHsr o
instance O.HasParentTypes DeviceHsr
type instance O.ParentTypes DeviceHsr = '[NM.Device.Device, NM.Object.Object, GObject.Object.Object]
toDeviceHsr :: (MIO.MonadIO m, IsDeviceHsr o) => o -> m DeviceHsr
toDeviceHsr :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceHsr o) =>
o -> m DeviceHsr
toDeviceHsr = IO DeviceHsr -> m DeviceHsr
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DeviceHsr -> m DeviceHsr)
-> (o -> IO DeviceHsr) -> o -> m DeviceHsr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DeviceHsr -> DeviceHsr) -> o -> IO DeviceHsr
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DeviceHsr -> DeviceHsr
DeviceHsr
instance B.GValue.IsGValue (Maybe DeviceHsr) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_nm_device_hsr_get_type
gvalueSet_ :: Ptr GValue -> Maybe DeviceHsr -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DeviceHsr
P.Nothing = Ptr GValue -> Ptr DeviceHsr -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DeviceHsr
forall a. Ptr a
FP.nullPtr :: FP.Ptr DeviceHsr)
gvalueSet_ Ptr GValue
gv (P.Just DeviceHsr
obj) = DeviceHsr -> (Ptr DeviceHsr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DeviceHsr
obj (Ptr GValue -> Ptr DeviceHsr -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DeviceHsr)
gvalueGet_ Ptr GValue
gv = do
Ptr DeviceHsr
ptr <- Ptr GValue -> IO (Ptr DeviceHsr)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DeviceHsr)
if Ptr DeviceHsr
ptr Ptr DeviceHsr -> Ptr DeviceHsr -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DeviceHsr
forall a. Ptr a
FP.nullPtr
then DeviceHsr -> Maybe DeviceHsr
forall a. a -> Maybe a
P.Just (DeviceHsr -> Maybe DeviceHsr)
-> IO DeviceHsr -> IO (Maybe DeviceHsr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DeviceHsr -> DeviceHsr)
-> Ptr DeviceHsr -> IO DeviceHsr
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DeviceHsr -> DeviceHsr
DeviceHsr Ptr DeviceHsr
ptr
else Maybe DeviceHsr -> IO (Maybe DeviceHsr)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeviceHsr
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceHsrMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDeviceHsrMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDeviceHsrMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDeviceHsrMethod "connectionCompatible" o = NM.Device.DeviceConnectionCompatibleMethodInfo
ResolveDeviceHsrMethod "connectionValid" o = NM.Device.DeviceConnectionValidMethodInfo
ResolveDeviceHsrMethod "delete" o = NM.Device.DeviceDeleteMethodInfo
ResolveDeviceHsrMethod "deleteAsync" o = NM.Device.DeviceDeleteAsyncMethodInfo
ResolveDeviceHsrMethod "deleteFinish" o = NM.Device.DeviceDeleteFinishMethodInfo
ResolveDeviceHsrMethod "disconnect" o = NM.Device.DeviceDisconnectMethodInfo
ResolveDeviceHsrMethod "disconnectAsync" o = NM.Device.DeviceDisconnectAsyncMethodInfo
ResolveDeviceHsrMethod "disconnectFinish" o = NM.Device.DeviceDisconnectFinishMethodInfo
ResolveDeviceHsrMethod "filterConnections" o = NM.Device.DeviceFilterConnectionsMethodInfo
ResolveDeviceHsrMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDeviceHsrMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDeviceHsrMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDeviceHsrMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDeviceHsrMethod "isReal" o = NM.Device.DeviceIsRealMethodInfo
ResolveDeviceHsrMethod "isSoftware" o = NM.Device.DeviceIsSoftwareMethodInfo
ResolveDeviceHsrMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDeviceHsrMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDeviceHsrMethod "reapply" o = NM.Device.DeviceReapplyMethodInfo
ResolveDeviceHsrMethod "reapplyAsync" o = NM.Device.DeviceReapplyAsyncMethodInfo
ResolveDeviceHsrMethod "reapplyFinish" o = NM.Device.DeviceReapplyFinishMethodInfo
ResolveDeviceHsrMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDeviceHsrMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDeviceHsrMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDeviceHsrMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDeviceHsrMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDeviceHsrMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDeviceHsrMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDeviceHsrMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDeviceHsrMethod "getActiveConnection" o = NM.Device.DeviceGetActiveConnectionMethodInfo
ResolveDeviceHsrMethod "getAppliedConnection" o = NM.Device.DeviceGetAppliedConnectionMethodInfo
ResolveDeviceHsrMethod "getAppliedConnectionAsync" o = NM.Device.DeviceGetAppliedConnectionAsyncMethodInfo
ResolveDeviceHsrMethod "getAppliedConnectionFinish" o = NM.Device.DeviceGetAppliedConnectionFinishMethodInfo
ResolveDeviceHsrMethod "getAutoconnect" o = NM.Device.DeviceGetAutoconnectMethodInfo
ResolveDeviceHsrMethod "getAvailableConnections" o = NM.Device.DeviceGetAvailableConnectionsMethodInfo
ResolveDeviceHsrMethod "getCapabilities" o = NM.Device.DeviceGetCapabilitiesMethodInfo
ResolveDeviceHsrMethod "getClient" o = NM.Object.ObjectGetClientMethodInfo
ResolveDeviceHsrMethod "getConnectivity" o = NM.Device.DeviceGetConnectivityMethodInfo
ResolveDeviceHsrMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDeviceHsrMethod "getDescription" o = NM.Device.DeviceGetDescriptionMethodInfo
ResolveDeviceHsrMethod "getDeviceType" o = NM.Device.DeviceGetDeviceTypeMethodInfo
ResolveDeviceHsrMethod "getDhcp4Config" o = NM.Device.DeviceGetDhcp4ConfigMethodInfo
ResolveDeviceHsrMethod "getDhcp6Config" o = NM.Device.DeviceGetDhcp6ConfigMethodInfo
ResolveDeviceHsrMethod "getDriver" o = NM.Device.DeviceGetDriverMethodInfo
ResolveDeviceHsrMethod "getDriverVersion" o = NM.Device.DeviceGetDriverVersionMethodInfo
ResolveDeviceHsrMethod "getFirmwareMissing" o = NM.Device.DeviceGetFirmwareMissingMethodInfo
ResolveDeviceHsrMethod "getFirmwareVersion" o = NM.Device.DeviceGetFirmwareVersionMethodInfo
ResolveDeviceHsrMethod "getHwAddress" o = NM.Device.DeviceGetHwAddressMethodInfo
ResolveDeviceHsrMethod "getIface" o = NM.Device.DeviceGetIfaceMethodInfo
ResolveDeviceHsrMethod "getInterfaceFlags" o = NM.Device.DeviceGetInterfaceFlagsMethodInfo
ResolveDeviceHsrMethod "getIp4Config" o = NM.Device.DeviceGetIp4ConfigMethodInfo
ResolveDeviceHsrMethod "getIp6Config" o = NM.Device.DeviceGetIp6ConfigMethodInfo
ResolveDeviceHsrMethod "getIpIface" o = NM.Device.DeviceGetIpIfaceMethodInfo
ResolveDeviceHsrMethod "getLldpNeighbors" o = NM.Device.DeviceGetLldpNeighborsMethodInfo
ResolveDeviceHsrMethod "getManaged" o = NM.Device.DeviceGetManagedMethodInfo
ResolveDeviceHsrMethod "getMetered" o = NM.Device.DeviceGetMeteredMethodInfo
ResolveDeviceHsrMethod "getMtu" o = NM.Device.DeviceGetMtuMethodInfo
ResolveDeviceHsrMethod "getMulticastSpec" o = DeviceHsrGetMulticastSpecMethodInfo
ResolveDeviceHsrMethod "getNmPluginMissing" o = NM.Device.DeviceGetNmPluginMissingMethodInfo
ResolveDeviceHsrMethod "getPath" o = NM.Device.DeviceGetPathMethodInfo
ResolveDeviceHsrMethod "getPhysicalPortId" o = NM.Device.DeviceGetPhysicalPortIdMethodInfo
ResolveDeviceHsrMethod "getPort1" o = DeviceHsrGetPort1MethodInfo
ResolveDeviceHsrMethod "getPort2" o = DeviceHsrGetPort2MethodInfo
ResolveDeviceHsrMethod "getPorts" o = NM.Device.DeviceGetPortsMethodInfo
ResolveDeviceHsrMethod "getProduct" o = NM.Device.DeviceGetProductMethodInfo
ResolveDeviceHsrMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDeviceHsrMethod "getPrp" o = DeviceHsrGetPrpMethodInfo
ResolveDeviceHsrMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDeviceHsrMethod "getSettingType" o = NM.Device.DeviceGetSettingTypeMethodInfo
ResolveDeviceHsrMethod "getState" o = NM.Device.DeviceGetStateMethodInfo
ResolveDeviceHsrMethod "getStateReason" o = NM.Device.DeviceGetStateReasonMethodInfo
ResolveDeviceHsrMethod "getSupervisionAddress" o = DeviceHsrGetSupervisionAddressMethodInfo
ResolveDeviceHsrMethod "getTypeDescription" o = NM.Device.DeviceGetTypeDescriptionMethodInfo
ResolveDeviceHsrMethod "getUdi" o = NM.Device.DeviceGetUdiMethodInfo
ResolveDeviceHsrMethod "getVendor" o = NM.Device.DeviceGetVendorMethodInfo
ResolveDeviceHsrMethod "setAutoconnect" o = NM.Device.DeviceSetAutoconnectMethodInfo
ResolveDeviceHsrMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDeviceHsrMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDeviceHsrMethod "setManaged" o = NM.Device.DeviceSetManagedMethodInfo
ResolveDeviceHsrMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDeviceHsrMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDeviceHsrMethod t DeviceHsr, O.OverloadedMethod info DeviceHsr p) => OL.IsLabel t (DeviceHsr -> 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 ~ ResolveDeviceHsrMethod t DeviceHsr, O.OverloadedMethod info DeviceHsr p, R.HasField t DeviceHsr p) => R.HasField t DeviceHsr p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDeviceHsrMethod t DeviceHsr, O.OverloadedMethodInfo info DeviceHsr) => OL.IsLabel t (O.MethodProxy info DeviceHsr) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
data DeviceHsrMulticastSpecPropertyInfo
instance AttrInfo DeviceHsrMulticastSpecPropertyInfo where
type AttrAllowedOps DeviceHsrMulticastSpecPropertyInfo = '[]
type AttrSetTypeConstraint DeviceHsrMulticastSpecPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceHsrMulticastSpecPropertyInfo = (~) ()
type AttrTransferType DeviceHsrMulticastSpecPropertyInfo = ()
type AttrBaseTypeConstraint DeviceHsrMulticastSpecPropertyInfo = (~) ()
type AttrGetType DeviceHsrMulticastSpecPropertyInfo = ()
type AttrLabel DeviceHsrMulticastSpecPropertyInfo = ""
type AttrOrigin DeviceHsrMulticastSpecPropertyInfo = DeviceHsr
attrGet = undefined
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
#endif
getDeviceHsrPort1 :: (MonadIO m, IsDeviceHsr o) => o -> m NM.Device.Device
getDeviceHsrPort1 :: forall (m :: * -> *) o. (MonadIO m, IsDeviceHsr o) => o -> m Device
getDeviceHsrPort1 o
obj = IO Device -> m Device
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Device -> m Device) -> IO Device -> m Device
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Device) -> IO Device
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDeviceHsrPort1" (IO (Maybe Device) -> IO Device) -> IO (Maybe Device) -> IO Device
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Device -> Device) -> IO (Maybe Device)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"port1" ManagedPtr Device -> Device
NM.Device.Device
#if defined(ENABLE_OVERLOADING)
data DeviceHsrPort1PropertyInfo
instance AttrInfo DeviceHsrPort1PropertyInfo where
type AttrAllowedOps DeviceHsrPort1PropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceHsrPort1PropertyInfo = IsDeviceHsr
type AttrSetTypeConstraint DeviceHsrPort1PropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceHsrPort1PropertyInfo = (~) ()
type AttrTransferType DeviceHsrPort1PropertyInfo = ()
type AttrGetType DeviceHsrPort1PropertyInfo = NM.Device.Device
type AttrLabel DeviceHsrPort1PropertyInfo = "port1"
type AttrOrigin DeviceHsrPort1PropertyInfo = DeviceHsr
attrGet = getDeviceHsrPort1
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.port1"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#g:attr:port1"
})
#endif
getDeviceHsrPort2 :: (MonadIO m, IsDeviceHsr o) => o -> m NM.Device.Device
getDeviceHsrPort2 :: forall (m :: * -> *) o. (MonadIO m, IsDeviceHsr o) => o -> m Device
getDeviceHsrPort2 o
obj = IO Device -> m Device
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Device -> m Device) -> IO Device -> m Device
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Device) -> IO Device
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDeviceHsrPort2" (IO (Maybe Device) -> IO Device) -> IO (Maybe Device) -> IO Device
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Device -> Device) -> IO (Maybe Device)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"port2" ManagedPtr Device -> Device
NM.Device.Device
#if defined(ENABLE_OVERLOADING)
data DeviceHsrPort2PropertyInfo
instance AttrInfo DeviceHsrPort2PropertyInfo where
type AttrAllowedOps DeviceHsrPort2PropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceHsrPort2PropertyInfo = IsDeviceHsr
type AttrSetTypeConstraint DeviceHsrPort2PropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceHsrPort2PropertyInfo = (~) ()
type AttrTransferType DeviceHsrPort2PropertyInfo = ()
type AttrGetType DeviceHsrPort2PropertyInfo = NM.Device.Device
type AttrLabel DeviceHsrPort2PropertyInfo = "port2"
type AttrOrigin DeviceHsrPort2PropertyInfo = DeviceHsr
attrGet = getDeviceHsrPort2
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.port2"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#g:attr:port2"
})
#endif
getDeviceHsrPrp :: (MonadIO m, IsDeviceHsr o) => o -> m Bool
getDeviceHsrPrp :: forall (m :: * -> *) o. (MonadIO m, IsDeviceHsr o) => o -> m Bool
getDeviceHsrPrp 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
"prp"
#if defined(ENABLE_OVERLOADING)
data DeviceHsrPrpPropertyInfo
instance AttrInfo DeviceHsrPrpPropertyInfo where
type AttrAllowedOps DeviceHsrPrpPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceHsrPrpPropertyInfo = IsDeviceHsr
type AttrSetTypeConstraint DeviceHsrPrpPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceHsrPrpPropertyInfo = (~) ()
type AttrTransferType DeviceHsrPrpPropertyInfo = ()
type AttrGetType DeviceHsrPrpPropertyInfo = Bool
type AttrLabel DeviceHsrPrpPropertyInfo = "prp"
type AttrOrigin DeviceHsrPrpPropertyInfo = DeviceHsr
attrGet = getDeviceHsrPrp
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.prp"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#g:attr:prp"
})
#endif
getDeviceHsrSupervisionAddress :: (MonadIO m, IsDeviceHsr o) => o -> m T.Text
getDeviceHsrSupervisionAddress :: forall (m :: * -> *) o. (MonadIO m, IsDeviceHsr o) => o -> m Text
getDeviceHsrSupervisionAddress 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
"getDeviceHsrSupervisionAddress" (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
"supervision-address"
#if defined(ENABLE_OVERLOADING)
data DeviceHsrSupervisionAddressPropertyInfo
instance AttrInfo DeviceHsrSupervisionAddressPropertyInfo where
type AttrAllowedOps DeviceHsrSupervisionAddressPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceHsrSupervisionAddressPropertyInfo = IsDeviceHsr
type AttrSetTypeConstraint DeviceHsrSupervisionAddressPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceHsrSupervisionAddressPropertyInfo = (~) ()
type AttrTransferType DeviceHsrSupervisionAddressPropertyInfo = ()
type AttrGetType DeviceHsrSupervisionAddressPropertyInfo = T.Text
type AttrLabel DeviceHsrSupervisionAddressPropertyInfo = "supervision-address"
type AttrOrigin DeviceHsrSupervisionAddressPropertyInfo = DeviceHsr
attrGet = getDeviceHsrSupervisionAddress
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.supervisionAddress"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#g:attr:supervisionAddress"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DeviceHsr
type instance O.AttributeList DeviceHsr = DeviceHsrAttributeList
type DeviceHsrAttributeList = ('[ '("activeConnection", NM.Device.DeviceActiveConnectionPropertyInfo), '("autoconnect", NM.Device.DeviceAutoconnectPropertyInfo), '("availableConnections", NM.Device.DeviceAvailableConnectionsPropertyInfo), '("capabilities", NM.Device.DeviceCapabilitiesPropertyInfo), '("client", NM.Object.ObjectClientPropertyInfo), '("deviceType", NM.Device.DeviceDeviceTypePropertyInfo), '("dhcp4Config", NM.Device.DeviceDhcp4ConfigPropertyInfo), '("dhcp6Config", NM.Device.DeviceDhcp6ConfigPropertyInfo), '("driver", NM.Device.DeviceDriverPropertyInfo), '("driverVersion", NM.Device.DeviceDriverVersionPropertyInfo), '("firmwareMissing", NM.Device.DeviceFirmwareMissingPropertyInfo), '("firmwareVersion", NM.Device.DeviceFirmwareVersionPropertyInfo), '("hwAddress", NM.Device.DeviceHwAddressPropertyInfo), '("interface", NM.Device.DeviceInterfacePropertyInfo), '("interfaceFlags", NM.Device.DeviceInterfaceFlagsPropertyInfo), '("ipInterface", NM.Device.DeviceIpInterfacePropertyInfo), '("ip4Config", NM.Device.DeviceIp4ConfigPropertyInfo), '("ip4Connectivity", NM.Device.DeviceIp4ConnectivityPropertyInfo), '("ip6Config", NM.Device.DeviceIp6ConfigPropertyInfo), '("ip6Connectivity", NM.Device.DeviceIp6ConnectivityPropertyInfo), '("lldpNeighbors", NM.Device.DeviceLldpNeighborsPropertyInfo), '("managed", NM.Device.DeviceManagedPropertyInfo), '("metered", NM.Device.DeviceMeteredPropertyInfo), '("mtu", NM.Device.DeviceMtuPropertyInfo), '("multicastSpec", DeviceHsrMulticastSpecPropertyInfo), '("nmPluginMissing", NM.Device.DeviceNmPluginMissingPropertyInfo), '("path", NM.Device.DevicePathPropertyInfo), '("physicalPortId", NM.Device.DevicePhysicalPortIdPropertyInfo), '("port1", DeviceHsrPort1PropertyInfo), '("port2", DeviceHsrPort2PropertyInfo), '("ports", NM.Device.DevicePortsPropertyInfo), '("product", NM.Device.DeviceProductPropertyInfo), '("prp", DeviceHsrPrpPropertyInfo), '("real", NM.Device.DeviceRealPropertyInfo), '("state", NM.Device.DeviceStatePropertyInfo), '("stateReason", NM.Device.DeviceStateReasonPropertyInfo), '("supervisionAddress", DeviceHsrSupervisionAddressPropertyInfo), '("udi", NM.Device.DeviceUdiPropertyInfo), '("vendor", NM.Device.DeviceVendorPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
deviceHsrMulticastSpec :: AttrLabelProxy "multicastSpec"
deviceHsrMulticastSpec = AttrLabelProxy
deviceHsrPort1 :: AttrLabelProxy "port1"
deviceHsrPort1 = AttrLabelProxy
deviceHsrPort2 :: AttrLabelProxy "port2"
deviceHsrPort2 = AttrLabelProxy
deviceHsrPrp :: AttrLabelProxy "prp"
deviceHsrPrp = AttrLabelProxy
deviceHsrSupervisionAddress :: AttrLabelProxy "supervisionAddress"
deviceHsrSupervisionAddress = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DeviceHsr = DeviceHsrSignalList
type DeviceHsrSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("stateChanged", NM.Device.DeviceStateChangedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "nm_device_hsr_get_multicast_spec" nm_device_hsr_get_multicast_spec ::
Ptr DeviceHsr ->
IO Word8
deviceHsrGetMulticastSpec ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceHsr a) =>
a
-> m Word8
deviceHsrGetMulticastSpec :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceHsr a) =>
a -> m Word8
deviceHsrGetMulticastSpec a
device = IO Word8 -> m Word8
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceHsr
device' <- a -> IO (Ptr DeviceHsr)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Word8
result <- Ptr DeviceHsr -> IO Word8
nm_device_hsr_get_multicast_spec Ptr DeviceHsr
device'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Word8 -> IO Word8
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result
#if defined(ENABLE_OVERLOADING)
data DeviceHsrGetMulticastSpecMethodInfo
instance (signature ~ (m Word8), MonadIO m, IsDeviceHsr a) => O.OverloadedMethod DeviceHsrGetMulticastSpecMethodInfo a signature where
overloadedMethod = deviceHsrGetMulticastSpec
instance O.OverloadedMethodInfo DeviceHsrGetMulticastSpecMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.deviceHsrGetMulticastSpec",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#v:deviceHsrGetMulticastSpec"
})
#endif
foreign import ccall "nm_device_hsr_get_port1" nm_device_hsr_get_port1 ::
Ptr DeviceHsr ->
IO (Ptr NM.Device.Device)
deviceHsrGetPort1 ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceHsr a) =>
a
-> m NM.Device.Device
deviceHsrGetPort1 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceHsr a) =>
a -> m Device
deviceHsrGetPort1 a
device = IO Device -> m Device
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Device -> m Device) -> IO Device -> m Device
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceHsr
device' <- a -> IO (Ptr DeviceHsr)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr Device
result <- Ptr DeviceHsr -> IO (Ptr Device)
nm_device_hsr_get_port1 Ptr DeviceHsr
device'
Text -> Ptr Device -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceHsrGetPort1" Ptr Device
result
Device
result' <- ((ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Device -> Device
NM.Device.Device) Ptr Device
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Device -> IO Device
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Device
result'
#if defined(ENABLE_OVERLOADING)
data DeviceHsrGetPort1MethodInfo
instance (signature ~ (m NM.Device.Device), MonadIO m, IsDeviceHsr a) => O.OverloadedMethod DeviceHsrGetPort1MethodInfo a signature where
overloadedMethod = deviceHsrGetPort1
instance O.OverloadedMethodInfo DeviceHsrGetPort1MethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.deviceHsrGetPort1",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#v:deviceHsrGetPort1"
})
#endif
foreign import ccall "nm_device_hsr_get_port2" nm_device_hsr_get_port2 ::
Ptr DeviceHsr ->
IO (Ptr NM.Device.Device)
deviceHsrGetPort2 ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceHsr a) =>
a
-> m NM.Device.Device
deviceHsrGetPort2 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceHsr a) =>
a -> m Device
deviceHsrGetPort2 a
device = IO Device -> m Device
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Device -> m Device) -> IO Device -> m Device
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceHsr
device' <- a -> IO (Ptr DeviceHsr)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
Ptr Device
result <- Ptr DeviceHsr -> IO (Ptr Device)
nm_device_hsr_get_port2 Ptr DeviceHsr
device'
Text -> Ptr Device -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceHsrGetPort2" Ptr Device
result
Device
result' <- ((ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Device -> Device
NM.Device.Device) Ptr Device
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Device -> IO Device
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Device
result'
#if defined(ENABLE_OVERLOADING)
data DeviceHsrGetPort2MethodInfo
instance (signature ~ (m NM.Device.Device), MonadIO m, IsDeviceHsr a) => O.OverloadedMethod DeviceHsrGetPort2MethodInfo a signature where
overloadedMethod = deviceHsrGetPort2
instance O.OverloadedMethodInfo DeviceHsrGetPort2MethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.deviceHsrGetPort2",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#v:deviceHsrGetPort2"
})
#endif
foreign import ccall "nm_device_hsr_get_prp" nm_device_hsr_get_prp ::
Ptr DeviceHsr ->
IO CInt
deviceHsrGetPrp ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceHsr a) =>
a
-> m Bool
deviceHsrGetPrp :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceHsr a) =>
a -> m Bool
deviceHsrGetPrp a
device = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceHsr
device' <- a -> IO (Ptr DeviceHsr)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CInt
result <- Ptr DeviceHsr -> IO CInt
nm_device_hsr_get_prp Ptr DeviceHsr
device'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DeviceHsrGetPrpMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDeviceHsr a) => O.OverloadedMethod DeviceHsrGetPrpMethodInfo a signature where
overloadedMethod = deviceHsrGetPrp
instance O.OverloadedMethodInfo DeviceHsrGetPrpMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.deviceHsrGetPrp",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#v:deviceHsrGetPrp"
})
#endif
foreign import ccall "nm_device_hsr_get_supervision_address" nm_device_hsr_get_supervision_address ::
Ptr DeviceHsr ->
IO CString
deviceHsrGetSupervisionAddress ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceHsr a) =>
a
-> m T.Text
deviceHsrGetSupervisionAddress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceHsr a) =>
a -> m Text
deviceHsrGetSupervisionAddress a
device = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceHsr
device' <- a -> IO (Ptr DeviceHsr)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
CString
result <- Ptr DeviceHsr -> IO CString
nm_device_hsr_get_supervision_address Ptr DeviceHsr
device'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceHsrGetSupervisionAddress" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DeviceHsrGetSupervisionAddressMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDeviceHsr a) => O.OverloadedMethod DeviceHsrGetSupervisionAddressMethodInfo a signature where
overloadedMethod = deviceHsrGetSupervisionAddress
instance O.OverloadedMethodInfo DeviceHsrGetSupervisionAddressMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceHsr.deviceHsrGetSupervisionAddress",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceHsr.html#v:deviceHsrGetSupervisionAddress"
})
#endif