{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.NM.Objects.DeviceWimax
(
DeviceWimax(..) ,
IsDeviceWimax ,
toDeviceWimax ,
#if defined(ENABLE_OVERLOADING)
ResolveDeviceWimaxMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetActiveNspMethodInfo ,
#endif
deviceWimaxGetActiveNsp ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetBsidMethodInfo ,
#endif
deviceWimaxGetBsid ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetCenterFrequencyMethodInfo ,
#endif
deviceWimaxGetCenterFrequency ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetCinrMethodInfo ,
#endif
deviceWimaxGetCinr ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetHwAddressMethodInfo ,
#endif
deviceWimaxGetHwAddress ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetNspByPathMethodInfo ,
#endif
deviceWimaxGetNspByPath ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetNspsMethodInfo ,
#endif
deviceWimaxGetNsps ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetRssiMethodInfo ,
#endif
deviceWimaxGetRssi ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxGetTxPowerMethodInfo ,
#endif
deviceWimaxGetTxPower ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxActiveNspPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxActiveNsp ,
#endif
getDeviceWimaxActiveNsp ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxBsidPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxBsid ,
#endif
getDeviceWimaxBsid ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxCenterFrequencyPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxCenterFrequency ,
#endif
getDeviceWimaxCenterFrequency ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxCinrPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxCinr ,
#endif
getDeviceWimaxCinr ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxHwAddressPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxHwAddress ,
#endif
getDeviceWimaxHwAddress ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxNspsPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxNsps ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceWimaxRssiPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxRssi ,
#endif
getDeviceWimaxRssi ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxTxPowerPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxTxPower ,
#endif
getDeviceWimaxTxPower ,
DeviceWimaxNspAddedCallback ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxNspAddedSignalInfo ,
#endif
afterDeviceWimaxNspAdded ,
onDeviceWimaxNspAdded ,
DeviceWimaxNspRemovedCallback ,
#if defined(ENABLE_OVERLOADING)
DeviceWimaxNspRemovedSignalInfo ,
#endif
afterDeviceWimaxNspRemoved ,
onDeviceWimaxNspRemoved ,
) 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.Objects.WimaxNsp as NM.WimaxNsp
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
import {-# SOURCE #-} qualified GI.NM.Objects.WimaxNsp as NM.WimaxNsp
#endif
newtype DeviceWimax = DeviceWimax (SP.ManagedPtr DeviceWimax)
deriving (DeviceWimax -> DeviceWimax -> Bool
(DeviceWimax -> DeviceWimax -> Bool)
-> (DeviceWimax -> DeviceWimax -> Bool) -> Eq DeviceWimax
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeviceWimax -> DeviceWimax -> Bool
== :: DeviceWimax -> DeviceWimax -> Bool
$c/= :: DeviceWimax -> DeviceWimax -> Bool
/= :: DeviceWimax -> DeviceWimax -> Bool
Eq)
instance SP.ManagedPtrNewtype DeviceWimax where
toManagedPtr :: DeviceWimax -> ManagedPtr DeviceWimax
toManagedPtr (DeviceWimax ManagedPtr DeviceWimax
p) = ManagedPtr DeviceWimax
p
foreign import ccall "nm_device_wimax_get_type"
c_nm_device_wimax_get_type :: IO B.Types.GType
instance B.Types.TypedObject DeviceWimax where
glibType :: IO GType
glibType = IO GType
c_nm_device_wimax_get_type
instance B.Types.GObject DeviceWimax
class (SP.GObject o, O.IsDescendantOf DeviceWimax o) => IsDeviceWimax o
instance (SP.GObject o, O.IsDescendantOf DeviceWimax o) => IsDeviceWimax o
instance O.HasParentTypes DeviceWimax
type instance O.ParentTypes DeviceWimax = '[NM.Device.Device, NM.Object.Object, GObject.Object.Object]
toDeviceWimax :: (MIO.MonadIO m, IsDeviceWimax o) => o -> m DeviceWimax
toDeviceWimax :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceWimax o) =>
o -> m DeviceWimax
toDeviceWimax = IO DeviceWimax -> m DeviceWimax
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DeviceWimax -> m DeviceWimax)
-> (o -> IO DeviceWimax) -> o -> m DeviceWimax
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DeviceWimax -> DeviceWimax) -> o -> IO DeviceWimax
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DeviceWimax -> DeviceWimax
DeviceWimax
instance B.GValue.IsGValue (Maybe DeviceWimax) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_nm_device_wimax_get_type
gvalueSet_ :: Ptr GValue -> Maybe DeviceWimax -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DeviceWimax
P.Nothing = Ptr GValue -> Ptr DeviceWimax -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DeviceWimax
forall a. Ptr a
FP.nullPtr :: FP.Ptr DeviceWimax)
gvalueSet_ Ptr GValue
gv (P.Just DeviceWimax
obj) = DeviceWimax -> (Ptr DeviceWimax -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DeviceWimax
obj (Ptr GValue -> Ptr DeviceWimax -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DeviceWimax)
gvalueGet_ Ptr GValue
gv = do
Ptr DeviceWimax
ptr <- Ptr GValue -> IO (Ptr DeviceWimax)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DeviceWimax)
if Ptr DeviceWimax
ptr Ptr DeviceWimax -> Ptr DeviceWimax -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DeviceWimax
forall a. Ptr a
FP.nullPtr
then DeviceWimax -> Maybe DeviceWimax
forall a. a -> Maybe a
P.Just (DeviceWimax -> Maybe DeviceWimax)
-> IO DeviceWimax -> IO (Maybe DeviceWimax)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DeviceWimax -> DeviceWimax)
-> Ptr DeviceWimax -> IO DeviceWimax
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DeviceWimax -> DeviceWimax
DeviceWimax Ptr DeviceWimax
ptr
else Maybe DeviceWimax -> IO (Maybe DeviceWimax)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeviceWimax
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceWimaxMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDeviceWimaxMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDeviceWimaxMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDeviceWimaxMethod "connectionCompatible" o = NM.Device.DeviceConnectionCompatibleMethodInfo
ResolveDeviceWimaxMethod "connectionValid" o = NM.Device.DeviceConnectionValidMethodInfo
ResolveDeviceWimaxMethod "delete" o = NM.Device.DeviceDeleteMethodInfo
ResolveDeviceWimaxMethod "deleteAsync" o = NM.Device.DeviceDeleteAsyncMethodInfo
ResolveDeviceWimaxMethod "deleteFinish" o = NM.Device.DeviceDeleteFinishMethodInfo
ResolveDeviceWimaxMethod "disconnect" o = NM.Device.DeviceDisconnectMethodInfo
ResolveDeviceWimaxMethod "disconnectAsync" o = NM.Device.DeviceDisconnectAsyncMethodInfo
ResolveDeviceWimaxMethod "disconnectFinish" o = NM.Device.DeviceDisconnectFinishMethodInfo
ResolveDeviceWimaxMethod "filterConnections" o = NM.Device.DeviceFilterConnectionsMethodInfo
ResolveDeviceWimaxMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDeviceWimaxMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDeviceWimaxMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDeviceWimaxMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDeviceWimaxMethod "isReal" o = NM.Device.DeviceIsRealMethodInfo
ResolveDeviceWimaxMethod "isSoftware" o = NM.Device.DeviceIsSoftwareMethodInfo
ResolveDeviceWimaxMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDeviceWimaxMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDeviceWimaxMethod "reapply" o = NM.Device.DeviceReapplyMethodInfo
ResolveDeviceWimaxMethod "reapplyAsync" o = NM.Device.DeviceReapplyAsyncMethodInfo
ResolveDeviceWimaxMethod "reapplyFinish" o = NM.Device.DeviceReapplyFinishMethodInfo
ResolveDeviceWimaxMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDeviceWimaxMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDeviceWimaxMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDeviceWimaxMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDeviceWimaxMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDeviceWimaxMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDeviceWimaxMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDeviceWimaxMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDeviceWimaxMethod "getActiveConnection" o = NM.Device.DeviceGetActiveConnectionMethodInfo
ResolveDeviceWimaxMethod "getActiveNsp" o = DeviceWimaxGetActiveNspMethodInfo
ResolveDeviceWimaxMethod "getAppliedConnection" o = NM.Device.DeviceGetAppliedConnectionMethodInfo
ResolveDeviceWimaxMethod "getAppliedConnectionAsync" o = NM.Device.DeviceGetAppliedConnectionAsyncMethodInfo
ResolveDeviceWimaxMethod "getAppliedConnectionFinish" o = NM.Device.DeviceGetAppliedConnectionFinishMethodInfo
ResolveDeviceWimaxMethod "getAutoconnect" o = NM.Device.DeviceGetAutoconnectMethodInfo
ResolveDeviceWimaxMethod "getAvailableConnections" o = NM.Device.DeviceGetAvailableConnectionsMethodInfo
ResolveDeviceWimaxMethod "getBsid" o = DeviceWimaxGetBsidMethodInfo
ResolveDeviceWimaxMethod "getCapabilities" o = NM.Device.DeviceGetCapabilitiesMethodInfo
ResolveDeviceWimaxMethod "getCenterFrequency" o = DeviceWimaxGetCenterFrequencyMethodInfo
ResolveDeviceWimaxMethod "getCinr" o = DeviceWimaxGetCinrMethodInfo
ResolveDeviceWimaxMethod "getClient" o = NM.Object.ObjectGetClientMethodInfo
ResolveDeviceWimaxMethod "getConnectivity" o = NM.Device.DeviceGetConnectivityMethodInfo
ResolveDeviceWimaxMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDeviceWimaxMethod "getDescription" o = NM.Device.DeviceGetDescriptionMethodInfo
ResolveDeviceWimaxMethod "getDeviceType" o = NM.Device.DeviceGetDeviceTypeMethodInfo
ResolveDeviceWimaxMethod "getDhcp4Config" o = NM.Device.DeviceGetDhcp4ConfigMethodInfo
ResolveDeviceWimaxMethod "getDhcp6Config" o = NM.Device.DeviceGetDhcp6ConfigMethodInfo
ResolveDeviceWimaxMethod "getDriver" o = NM.Device.DeviceGetDriverMethodInfo
ResolveDeviceWimaxMethod "getDriverVersion" o = NM.Device.DeviceGetDriverVersionMethodInfo
ResolveDeviceWimaxMethod "getFirmwareMissing" o = NM.Device.DeviceGetFirmwareMissingMethodInfo
ResolveDeviceWimaxMethod "getFirmwareVersion" o = NM.Device.DeviceGetFirmwareVersionMethodInfo
ResolveDeviceWimaxMethod "getHwAddress" o = DeviceWimaxGetHwAddressMethodInfo
ResolveDeviceWimaxMethod "getIface" o = NM.Device.DeviceGetIfaceMethodInfo
ResolveDeviceWimaxMethod "getInterfaceFlags" o = NM.Device.DeviceGetInterfaceFlagsMethodInfo
ResolveDeviceWimaxMethod "getIp4Config" o = NM.Device.DeviceGetIp4ConfigMethodInfo
ResolveDeviceWimaxMethod "getIp6Config" o = NM.Device.DeviceGetIp6ConfigMethodInfo
ResolveDeviceWimaxMethod "getIpIface" o = NM.Device.DeviceGetIpIfaceMethodInfo
ResolveDeviceWimaxMethod "getLldpNeighbors" o = NM.Device.DeviceGetLldpNeighborsMethodInfo
ResolveDeviceWimaxMethod "getManaged" o = NM.Device.DeviceGetManagedMethodInfo
ResolveDeviceWimaxMethod "getMetered" o = NM.Device.DeviceGetMeteredMethodInfo
ResolveDeviceWimaxMethod "getMtu" o = NM.Device.DeviceGetMtuMethodInfo
ResolveDeviceWimaxMethod "getNmPluginMissing" o = NM.Device.DeviceGetNmPluginMissingMethodInfo
ResolveDeviceWimaxMethod "getNspByPath" o = DeviceWimaxGetNspByPathMethodInfo
ResolveDeviceWimaxMethod "getNsps" o = DeviceWimaxGetNspsMethodInfo
ResolveDeviceWimaxMethod "getPath" o = NM.Device.DeviceGetPathMethodInfo
ResolveDeviceWimaxMethod "getPhysicalPortId" o = NM.Device.DeviceGetPhysicalPortIdMethodInfo
ResolveDeviceWimaxMethod "getPorts" o = NM.Device.DeviceGetPortsMethodInfo
ResolveDeviceWimaxMethod "getProduct" o = NM.Device.DeviceGetProductMethodInfo
ResolveDeviceWimaxMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDeviceWimaxMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDeviceWimaxMethod "getRssi" o = DeviceWimaxGetRssiMethodInfo
ResolveDeviceWimaxMethod "getSettingType" o = NM.Device.DeviceGetSettingTypeMethodInfo
ResolveDeviceWimaxMethod "getState" o = NM.Device.DeviceGetStateMethodInfo
ResolveDeviceWimaxMethod "getStateReason" o = NM.Device.DeviceGetStateReasonMethodInfo
ResolveDeviceWimaxMethod "getTxPower" o = DeviceWimaxGetTxPowerMethodInfo
ResolveDeviceWimaxMethod "getTypeDescription" o = NM.Device.DeviceGetTypeDescriptionMethodInfo
ResolveDeviceWimaxMethod "getUdi" o = NM.Device.DeviceGetUdiMethodInfo
ResolveDeviceWimaxMethod "getVendor" o = NM.Device.DeviceGetVendorMethodInfo
ResolveDeviceWimaxMethod "setAutoconnect" o = NM.Device.DeviceSetAutoconnectMethodInfo
ResolveDeviceWimaxMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDeviceWimaxMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDeviceWimaxMethod "setManaged" o = NM.Device.DeviceSetManagedMethodInfo
ResolveDeviceWimaxMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDeviceWimaxMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDeviceWimaxMethod t DeviceWimax, O.OverloadedMethod info DeviceWimax p) => OL.IsLabel t (DeviceWimax -> 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 ~ ResolveDeviceWimaxMethod t DeviceWimax, O.OverloadedMethod info DeviceWimax p, R.HasField t DeviceWimax p) => R.HasField t DeviceWimax p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDeviceWimaxMethod t DeviceWimax, O.OverloadedMethodInfo info DeviceWimax) => OL.IsLabel t (O.MethodProxy info DeviceWimax) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
{-# DEPRECATED DeviceWimaxNspAddedCallback ["(Since version 1.2)","WiMAX is no longer supported."] #-}
type DeviceWimaxNspAddedCallback =
GObject.Object.Object
-> IO ()
type C_DeviceWimaxNspAddedCallback =
Ptr DeviceWimax ->
Ptr GObject.Object.Object ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DeviceWimaxNspAddedCallback :: C_DeviceWimaxNspAddedCallback -> IO (FunPtr C_DeviceWimaxNspAddedCallback)
wrap_DeviceWimaxNspAddedCallback ::
GObject a => (a -> DeviceWimaxNspAddedCallback) ->
C_DeviceWimaxNspAddedCallback
wrap_DeviceWimaxNspAddedCallback :: forall a.
GObject a =>
(a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
wrap_DeviceWimaxNspAddedCallback a -> DeviceWimaxNspAddedCallback
gi'cb Ptr DeviceWimax
gi'selfPtr Ptr Object
nsp Ptr ()
_ = do
Object
nsp' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
nsp
Ptr DeviceWimax -> (DeviceWimax -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DeviceWimax
gi'selfPtr ((DeviceWimax -> IO ()) -> IO ())
-> (DeviceWimax -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DeviceWimax
gi'self -> a -> DeviceWimaxNspAddedCallback
gi'cb (DeviceWimax -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DeviceWimax
gi'self) Object
nsp'
onDeviceWimaxNspAdded :: (IsDeviceWimax a, MonadIO m) => a -> ((?self :: a) => DeviceWimaxNspAddedCallback) -> m SignalHandlerId
onDeviceWimaxNspAdded :: forall a (m :: * -> *).
(IsDeviceWimax a, MonadIO m) =>
a
-> ((?self::a) => DeviceWimaxNspAddedCallback) -> m SignalHandlerId
onDeviceWimaxNspAdded a
obj (?self::a) => DeviceWimaxNspAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> DeviceWimaxNspAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceWimaxNspAddedCallback
DeviceWimaxNspAddedCallback
cb
let wrapped' :: C_DeviceWimaxNspAddedCallback
wrapped' = (a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
forall a.
GObject a =>
(a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
wrap_DeviceWimaxNspAddedCallback a -> DeviceWimaxNspAddedCallback
wrapped
FunPtr C_DeviceWimaxNspAddedCallback
wrapped'' <- C_DeviceWimaxNspAddedCallback
-> IO (FunPtr C_DeviceWimaxNspAddedCallback)
mk_DeviceWimaxNspAddedCallback C_DeviceWimaxNspAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceWimaxNspAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"nsp-added" FunPtr C_DeviceWimaxNspAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDeviceWimaxNspAdded :: (IsDeviceWimax a, MonadIO m) => a -> ((?self :: a) => DeviceWimaxNspAddedCallback) -> m SignalHandlerId
afterDeviceWimaxNspAdded :: forall a (m :: * -> *).
(IsDeviceWimax a, MonadIO m) =>
a
-> ((?self::a) => DeviceWimaxNspAddedCallback) -> m SignalHandlerId
afterDeviceWimaxNspAdded a
obj (?self::a) => DeviceWimaxNspAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> DeviceWimaxNspAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceWimaxNspAddedCallback
DeviceWimaxNspAddedCallback
cb
let wrapped' :: C_DeviceWimaxNspAddedCallback
wrapped' = (a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
forall a.
GObject a =>
(a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
wrap_DeviceWimaxNspAddedCallback a -> DeviceWimaxNspAddedCallback
wrapped
FunPtr C_DeviceWimaxNspAddedCallback
wrapped'' <- C_DeviceWimaxNspAddedCallback
-> IO (FunPtr C_DeviceWimaxNspAddedCallback)
mk_DeviceWimaxNspAddedCallback C_DeviceWimaxNspAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceWimaxNspAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"nsp-added" FunPtr C_DeviceWimaxNspAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxNspAddedSignalInfo
instance SignalInfo DeviceWimaxNspAddedSignalInfo where
type HaskellCallbackType DeviceWimaxNspAddedSignalInfo = DeviceWimaxNspAddedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DeviceWimaxNspAddedCallback cb
cb'' <- mk_DeviceWimaxNspAddedCallback cb'
connectSignalFunPtr obj "nsp-added" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax::nsp-added"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:signal:nspAdded"})
#endif
{-# DEPRECATED DeviceWimaxNspRemovedCallback ["(Since version 1.2)","WiMAX is no longer supported."] #-}
type DeviceWimaxNspRemovedCallback =
GObject.Object.Object
-> IO ()
type C_DeviceWimaxNspRemovedCallback =
Ptr DeviceWimax ->
Ptr GObject.Object.Object ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DeviceWimaxNspRemovedCallback :: C_DeviceWimaxNspRemovedCallback -> IO (FunPtr C_DeviceWimaxNspRemovedCallback)
wrap_DeviceWimaxNspRemovedCallback ::
GObject a => (a -> DeviceWimaxNspRemovedCallback) ->
C_DeviceWimaxNspRemovedCallback
wrap_DeviceWimaxNspRemovedCallback :: forall a.
GObject a =>
(a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
wrap_DeviceWimaxNspRemovedCallback a -> DeviceWimaxNspAddedCallback
gi'cb Ptr DeviceWimax
gi'selfPtr Ptr Object
nsp Ptr ()
_ = do
Object
nsp' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
nsp
Ptr DeviceWimax -> (DeviceWimax -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DeviceWimax
gi'selfPtr ((DeviceWimax -> IO ()) -> IO ())
-> (DeviceWimax -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DeviceWimax
gi'self -> a -> DeviceWimaxNspAddedCallback
gi'cb (DeviceWimax -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DeviceWimax
gi'self) Object
nsp'
onDeviceWimaxNspRemoved :: (IsDeviceWimax a, MonadIO m) => a -> ((?self :: a) => DeviceWimaxNspRemovedCallback) -> m SignalHandlerId
onDeviceWimaxNspRemoved :: forall a (m :: * -> *).
(IsDeviceWimax a, MonadIO m) =>
a
-> ((?self::a) => DeviceWimaxNspAddedCallback) -> m SignalHandlerId
onDeviceWimaxNspRemoved a
obj (?self::a) => DeviceWimaxNspAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> DeviceWimaxNspAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceWimaxNspAddedCallback
DeviceWimaxNspAddedCallback
cb
let wrapped' :: C_DeviceWimaxNspAddedCallback
wrapped' = (a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
forall a.
GObject a =>
(a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
wrap_DeviceWimaxNspRemovedCallback a -> DeviceWimaxNspAddedCallback
wrapped
FunPtr C_DeviceWimaxNspAddedCallback
wrapped'' <- C_DeviceWimaxNspAddedCallback
-> IO (FunPtr C_DeviceWimaxNspAddedCallback)
mk_DeviceWimaxNspRemovedCallback C_DeviceWimaxNspAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceWimaxNspAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"nsp-removed" FunPtr C_DeviceWimaxNspAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDeviceWimaxNspRemoved :: (IsDeviceWimax a, MonadIO m) => a -> ((?self :: a) => DeviceWimaxNspRemovedCallback) -> m SignalHandlerId
afterDeviceWimaxNspRemoved :: forall a (m :: * -> *).
(IsDeviceWimax a, MonadIO m) =>
a
-> ((?self::a) => DeviceWimaxNspAddedCallback) -> m SignalHandlerId
afterDeviceWimaxNspRemoved a
obj (?self::a) => DeviceWimaxNspAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> DeviceWimaxNspAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceWimaxNspAddedCallback
DeviceWimaxNspAddedCallback
cb
let wrapped' :: C_DeviceWimaxNspAddedCallback
wrapped' = (a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
forall a.
GObject a =>
(a -> DeviceWimaxNspAddedCallback) -> C_DeviceWimaxNspAddedCallback
wrap_DeviceWimaxNspRemovedCallback a -> DeviceWimaxNspAddedCallback
wrapped
FunPtr C_DeviceWimaxNspAddedCallback
wrapped'' <- C_DeviceWimaxNspAddedCallback
-> IO (FunPtr C_DeviceWimaxNspAddedCallback)
mk_DeviceWimaxNspRemovedCallback C_DeviceWimaxNspAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceWimaxNspAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"nsp-removed" FunPtr C_DeviceWimaxNspAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxNspRemovedSignalInfo
instance SignalInfo DeviceWimaxNspRemovedSignalInfo where
type HaskellCallbackType DeviceWimaxNspRemovedSignalInfo = DeviceWimaxNspRemovedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DeviceWimaxNspRemovedCallback cb
cb'' <- mk_DeviceWimaxNspRemovedCallback cb'
connectSignalFunPtr obj "nsp-removed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax::nsp-removed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:signal:nspRemoved"})
#endif
getDeviceWimaxActiveNsp :: (MonadIO m, IsDeviceWimax o) => o -> m (Maybe NM.WimaxNsp.WimaxNsp)
getDeviceWimaxActiveNsp :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceWimax o) =>
o -> m (Maybe WimaxNsp)
getDeviceWimaxActiveNsp o
obj = IO (Maybe WimaxNsp) -> m (Maybe WimaxNsp)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe WimaxNsp) -> m (Maybe WimaxNsp))
-> IO (Maybe WimaxNsp) -> m (Maybe WimaxNsp)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr WimaxNsp -> WimaxNsp)
-> IO (Maybe WimaxNsp)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"active-nsp" ManagedPtr WimaxNsp -> WimaxNsp
NM.WimaxNsp.WimaxNsp
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxActiveNspPropertyInfo
instance AttrInfo DeviceWimaxActiveNspPropertyInfo where
type AttrAllowedOps DeviceWimaxActiveNspPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceWimaxActiveNspPropertyInfo = IsDeviceWimax
type AttrSetTypeConstraint DeviceWimaxActiveNspPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceWimaxActiveNspPropertyInfo = (~) ()
type AttrTransferType DeviceWimaxActiveNspPropertyInfo = ()
type AttrGetType DeviceWimaxActiveNspPropertyInfo = (Maybe NM.WimaxNsp.WimaxNsp)
type AttrLabel DeviceWimaxActiveNspPropertyInfo = "active-nsp"
type AttrOrigin DeviceWimaxActiveNspPropertyInfo = DeviceWimax
attrGet = getDeviceWimaxActiveNsp
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.activeNsp"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:attr:activeNsp"
})
#endif
getDeviceWimaxBsid :: (MonadIO m, IsDeviceWimax o) => o -> m T.Text
getDeviceWimaxBsid :: forall (m :: * -> *) o. (MonadIO m, IsDeviceWimax o) => o -> m Text
getDeviceWimaxBsid 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
"getDeviceWimaxBsid" (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
"bsid"
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxBsidPropertyInfo
instance AttrInfo DeviceWimaxBsidPropertyInfo where
type AttrAllowedOps DeviceWimaxBsidPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceWimaxBsidPropertyInfo = IsDeviceWimax
type AttrSetTypeConstraint DeviceWimaxBsidPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceWimaxBsidPropertyInfo = (~) ()
type AttrTransferType DeviceWimaxBsidPropertyInfo = ()
type AttrGetType DeviceWimaxBsidPropertyInfo = T.Text
type AttrLabel DeviceWimaxBsidPropertyInfo = "bsid"
type AttrOrigin DeviceWimaxBsidPropertyInfo = DeviceWimax
attrGet = getDeviceWimaxBsid
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.bsid"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:attr:bsid"
})
#endif
getDeviceWimaxCenterFrequency :: (MonadIO m, IsDeviceWimax o) => o -> m Word32
getDeviceWimaxCenterFrequency :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceWimax o) =>
o -> m Word32
getDeviceWimaxCenterFrequency 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
"center-frequency"
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxCenterFrequencyPropertyInfo
instance AttrInfo DeviceWimaxCenterFrequencyPropertyInfo where
type AttrAllowedOps DeviceWimaxCenterFrequencyPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceWimaxCenterFrequencyPropertyInfo = IsDeviceWimax
type AttrSetTypeConstraint DeviceWimaxCenterFrequencyPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceWimaxCenterFrequencyPropertyInfo = (~) ()
type AttrTransferType DeviceWimaxCenterFrequencyPropertyInfo = ()
type AttrGetType DeviceWimaxCenterFrequencyPropertyInfo = Word32
type AttrLabel DeviceWimaxCenterFrequencyPropertyInfo = "center-frequency"
type AttrOrigin DeviceWimaxCenterFrequencyPropertyInfo = DeviceWimax
attrGet = getDeviceWimaxCenterFrequency
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.centerFrequency"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:attr:centerFrequency"
})
#endif
getDeviceWimaxCinr :: (MonadIO m, IsDeviceWimax o) => o -> m Int32
getDeviceWimaxCinr :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceWimax o) =>
o -> m Int32
getDeviceWimaxCinr o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"cinr"
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxCinrPropertyInfo
instance AttrInfo DeviceWimaxCinrPropertyInfo where
type AttrAllowedOps DeviceWimaxCinrPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceWimaxCinrPropertyInfo = IsDeviceWimax
type AttrSetTypeConstraint DeviceWimaxCinrPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceWimaxCinrPropertyInfo = (~) ()
type AttrTransferType DeviceWimaxCinrPropertyInfo = ()
type AttrGetType DeviceWimaxCinrPropertyInfo = Int32
type AttrLabel DeviceWimaxCinrPropertyInfo = "cinr"
type AttrOrigin DeviceWimaxCinrPropertyInfo = DeviceWimax
attrGet = getDeviceWimaxCinr
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.cinr"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:attr:cinr"
})
#endif
getDeviceWimaxHwAddress :: (MonadIO m, IsDeviceWimax o) => o -> m T.Text
getDeviceWimaxHwAddress :: forall (m :: * -> *) o. (MonadIO m, IsDeviceWimax o) => o -> m Text
getDeviceWimaxHwAddress 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
"getDeviceWimaxHwAddress" (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
"hw-address"
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxHwAddressPropertyInfo
instance AttrInfo DeviceWimaxHwAddressPropertyInfo where
type AttrAllowedOps DeviceWimaxHwAddressPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceWimaxHwAddressPropertyInfo = IsDeviceWimax
type AttrSetTypeConstraint DeviceWimaxHwAddressPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceWimaxHwAddressPropertyInfo = (~) ()
type AttrTransferType DeviceWimaxHwAddressPropertyInfo = ()
type AttrGetType DeviceWimaxHwAddressPropertyInfo = T.Text
type AttrLabel DeviceWimaxHwAddressPropertyInfo = "hw-address"
type AttrOrigin DeviceWimaxHwAddressPropertyInfo = DeviceWimax
attrGet = getDeviceWimaxHwAddress
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.hwAddress"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:attr:hwAddress"
})
#endif
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxNspsPropertyInfo
instance AttrInfo DeviceWimaxNspsPropertyInfo where
type AttrAllowedOps DeviceWimaxNspsPropertyInfo = '[]
type AttrSetTypeConstraint DeviceWimaxNspsPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceWimaxNspsPropertyInfo = (~) ()
type AttrTransferType DeviceWimaxNspsPropertyInfo = ()
type AttrBaseTypeConstraint DeviceWimaxNspsPropertyInfo = (~) ()
type AttrGetType DeviceWimaxNspsPropertyInfo = ()
type AttrLabel DeviceWimaxNspsPropertyInfo = ""
type AttrOrigin DeviceWimaxNspsPropertyInfo = DeviceWimax
attrGet = undefined
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
#endif
getDeviceWimaxRssi :: (MonadIO m, IsDeviceWimax o) => o -> m Int32
o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"rssi"
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxRssiPropertyInfo
instance AttrInfo DeviceWimaxRssiPropertyInfo where
type AttrAllowedOps DeviceWimaxRssiPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceWimaxRssiPropertyInfo = IsDeviceWimax
type AttrSetTypeConstraint DeviceWimaxRssiPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceWimaxRssiPropertyInfo = (~) ()
type AttrTransferType DeviceWimaxRssiPropertyInfo = ()
type AttrGetType DeviceWimaxRssiPropertyInfo = Int32
type AttrLabel DeviceWimaxRssiPropertyInfo = "rssi"
type AttrOrigin DeviceWimaxRssiPropertyInfo = DeviceWimax
attrGet = getDeviceWimaxRssi
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.rssi"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:attr:rssi"
})
#endif
getDeviceWimaxTxPower :: (MonadIO m, IsDeviceWimax o) => o -> m Int32
getDeviceWimaxTxPower :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceWimax o) =>
o -> m Int32
getDeviceWimaxTxPower o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"tx-power"
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxTxPowerPropertyInfo
instance AttrInfo DeviceWimaxTxPowerPropertyInfo where
type AttrAllowedOps DeviceWimaxTxPowerPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DeviceWimaxTxPowerPropertyInfo = IsDeviceWimax
type AttrSetTypeConstraint DeviceWimaxTxPowerPropertyInfo = (~) ()
type AttrTransferTypeConstraint DeviceWimaxTxPowerPropertyInfo = (~) ()
type AttrTransferType DeviceWimaxTxPowerPropertyInfo = ()
type AttrGetType DeviceWimaxTxPowerPropertyInfo = Int32
type AttrLabel DeviceWimaxTxPowerPropertyInfo = "tx-power"
type AttrOrigin DeviceWimaxTxPowerPropertyInfo = DeviceWimax
attrGet = getDeviceWimaxTxPower
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.txPower"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#g:attr:txPower"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DeviceWimax
type instance O.AttributeList DeviceWimax = DeviceWimaxAttributeList
type DeviceWimaxAttributeList = ('[ '("activeConnection", NM.Device.DeviceActiveConnectionPropertyInfo), '("activeNsp", DeviceWimaxActiveNspPropertyInfo), '("autoconnect", NM.Device.DeviceAutoconnectPropertyInfo), '("availableConnections", NM.Device.DeviceAvailableConnectionsPropertyInfo), '("bsid", DeviceWimaxBsidPropertyInfo), '("capabilities", NM.Device.DeviceCapabilitiesPropertyInfo), '("centerFrequency", DeviceWimaxCenterFrequencyPropertyInfo), '("cinr", DeviceWimaxCinrPropertyInfo), '("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", DeviceWimaxHwAddressPropertyInfo), '("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), '("nmPluginMissing", NM.Device.DeviceNmPluginMissingPropertyInfo), '("nsps", DeviceWimaxNspsPropertyInfo), '("path", NM.Device.DevicePathPropertyInfo), '("physicalPortId", NM.Device.DevicePhysicalPortIdPropertyInfo), '("ports", NM.Device.DevicePortsPropertyInfo), '("product", NM.Device.DeviceProductPropertyInfo), '("real", NM.Device.DeviceRealPropertyInfo), '("rssi", DeviceWimaxRssiPropertyInfo), '("state", NM.Device.DeviceStatePropertyInfo), '("stateReason", NM.Device.DeviceStateReasonPropertyInfo), '("txPower", DeviceWimaxTxPowerPropertyInfo), '("udi", NM.Device.DeviceUdiPropertyInfo), '("vendor", NM.Device.DeviceVendorPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
deviceWimaxActiveNsp :: AttrLabelProxy "activeNsp"
deviceWimaxActiveNsp = AttrLabelProxy
deviceWimaxBsid :: AttrLabelProxy "bsid"
deviceWimaxBsid = AttrLabelProxy
deviceWimaxCenterFrequency :: AttrLabelProxy "centerFrequency"
deviceWimaxCenterFrequency = AttrLabelProxy
deviceWimaxCinr :: AttrLabelProxy "cinr"
deviceWimaxCinr = AttrLabelProxy
deviceWimaxHwAddress :: AttrLabelProxy "hwAddress"
deviceWimaxHwAddress = AttrLabelProxy
deviceWimaxNsps :: AttrLabelProxy "nsps"
deviceWimaxNsps = AttrLabelProxy
deviceWimaxRssi :: AttrLabelProxy "rssi"
deviceWimaxRssi = AttrLabelProxy
deviceWimaxTxPower :: AttrLabelProxy "txPower"
deviceWimaxTxPower = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DeviceWimax = DeviceWimaxSignalList
type DeviceWimaxSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("nspAdded", DeviceWimaxNspAddedSignalInfo), '("nspRemoved", DeviceWimaxNspRemovedSignalInfo), '("stateChanged", NM.Device.DeviceStateChangedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "nm_device_wimax_get_active_nsp" nm_device_wimax_get_active_nsp ::
Ptr DeviceWimax ->
IO (Ptr NM.WimaxNsp.WimaxNsp)
{-# DEPRECATED deviceWimaxGetActiveNsp ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetActiveNsp ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> m NM.WimaxNsp.WimaxNsp
deviceWimaxGetActiveNsp :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceWimax a) =>
a -> m WimaxNsp
deviceWimaxGetActiveNsp a
wimax = IO WimaxNsp -> m WimaxNsp
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WimaxNsp -> m WimaxNsp) -> IO WimaxNsp -> m WimaxNsp
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceWimax
wimax' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
wimax
Ptr WimaxNsp
result <- Ptr DeviceWimax -> IO (Ptr WimaxNsp)
nm_device_wimax_get_active_nsp Ptr DeviceWimax
wimax'
Text -> Ptr WimaxNsp -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceWimaxGetActiveNsp" Ptr WimaxNsp
result
WimaxNsp
result' <- ((ManagedPtr WimaxNsp -> WimaxNsp) -> Ptr WimaxNsp -> IO WimaxNsp
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr WimaxNsp -> WimaxNsp
NM.WimaxNsp.WimaxNsp) Ptr WimaxNsp
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
wimax
WimaxNsp -> IO WimaxNsp
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WimaxNsp
result'
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetActiveNspMethodInfo
instance (signature ~ (m NM.WimaxNsp.WimaxNsp), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetActiveNspMethodInfo a signature where
overloadedMethod = deviceWimaxGetActiveNsp
instance O.OverloadedMethodInfo DeviceWimaxGetActiveNspMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetActiveNsp",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetActiveNsp"
})
#endif
foreign import ccall "nm_device_wimax_get_bsid" nm_device_wimax_get_bsid ::
Ptr DeviceWimax ->
IO CString
{-# DEPRECATED deviceWimaxGetBsid ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetBsid ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> m T.Text
deviceWimaxGetBsid :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceWimax a) =>
a -> m Text
deviceWimaxGetBsid a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceWimax
self' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr DeviceWimax -> IO CString
nm_device_wimax_get_bsid Ptr DeviceWimax
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceWimaxGetBsid" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetBsidMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetBsidMethodInfo a signature where
overloadedMethod = deviceWimaxGetBsid
instance O.OverloadedMethodInfo DeviceWimaxGetBsidMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetBsid",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetBsid"
})
#endif
foreign import ccall "nm_device_wimax_get_center_frequency" nm_device_wimax_get_center_frequency ::
Ptr DeviceWimax ->
IO Word32
{-# DEPRECATED deviceWimaxGetCenterFrequency ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetCenterFrequency ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> m Word32
deviceWimaxGetCenterFrequency :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceWimax a) =>
a -> m Word32
deviceWimaxGetCenterFrequency a
self = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceWimax
self' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Word32
result <- Ptr DeviceWimax -> IO Word32
nm_device_wimax_get_center_frequency Ptr DeviceWimax
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetCenterFrequencyMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetCenterFrequencyMethodInfo a signature where
overloadedMethod = deviceWimaxGetCenterFrequency
instance O.OverloadedMethodInfo DeviceWimaxGetCenterFrequencyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetCenterFrequency",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetCenterFrequency"
})
#endif
foreign import ccall "nm_device_wimax_get_cinr" nm_device_wimax_get_cinr ::
Ptr DeviceWimax ->
IO Int32
{-# DEPRECATED deviceWimaxGetCinr ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetCinr ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> m Int32
deviceWimaxGetCinr :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceWimax a) =>
a -> m Int32
deviceWimaxGetCinr a
self = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceWimax
self' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Int32
result <- Ptr DeviceWimax -> IO Int32
nm_device_wimax_get_cinr Ptr DeviceWimax
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetCinrMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetCinrMethodInfo a signature where
overloadedMethod = deviceWimaxGetCinr
instance O.OverloadedMethodInfo DeviceWimaxGetCinrMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetCinr",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetCinr"
})
#endif
foreign import ccall "nm_device_wimax_get_hw_address" nm_device_wimax_get_hw_address ::
Ptr DeviceWimax ->
IO CString
{-# DEPRECATED deviceWimaxGetHwAddress ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetHwAddress ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> m T.Text
deviceWimaxGetHwAddress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceWimax a) =>
a -> m Text
deviceWimaxGetHwAddress a
wimax = 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 DeviceWimax
wimax' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
wimax
CString
result <- Ptr DeviceWimax -> IO CString
nm_device_wimax_get_hw_address Ptr DeviceWimax
wimax'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceWimaxGetHwAddress" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
wimax
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetHwAddressMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetHwAddressMethodInfo a signature where
overloadedMethod = deviceWimaxGetHwAddress
instance O.OverloadedMethodInfo DeviceWimaxGetHwAddressMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetHwAddress",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetHwAddress"
})
#endif
foreign import ccall "nm_device_wimax_get_nsp_by_path" nm_device_wimax_get_nsp_by_path ::
Ptr DeviceWimax ->
CString ->
IO (Ptr NM.WimaxNsp.WimaxNsp)
{-# DEPRECATED deviceWimaxGetNspByPath ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetNspByPath ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> T.Text
-> m NM.WimaxNsp.WimaxNsp
deviceWimaxGetNspByPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceWimax a) =>
a -> Text -> m WimaxNsp
deviceWimaxGetNspByPath a
wimax Text
path = IO WimaxNsp -> m WimaxNsp
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WimaxNsp -> m WimaxNsp) -> IO WimaxNsp -> m WimaxNsp
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceWimax
wimax' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
wimax
CString
path' <- Text -> IO CString
textToCString Text
path
Ptr WimaxNsp
result <- Ptr DeviceWimax -> CString -> IO (Ptr WimaxNsp)
nm_device_wimax_get_nsp_by_path Ptr DeviceWimax
wimax' CString
path'
Text -> Ptr WimaxNsp -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceWimaxGetNspByPath" Ptr WimaxNsp
result
WimaxNsp
result' <- ((ManagedPtr WimaxNsp -> WimaxNsp) -> Ptr WimaxNsp -> IO WimaxNsp
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr WimaxNsp -> WimaxNsp
NM.WimaxNsp.WimaxNsp) Ptr WimaxNsp
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
wimax
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
WimaxNsp -> IO WimaxNsp
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WimaxNsp
result'
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetNspByPathMethodInfo
instance (signature ~ (T.Text -> m NM.WimaxNsp.WimaxNsp), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetNspByPathMethodInfo a signature where
overloadedMethod = deviceWimaxGetNspByPath
instance O.OverloadedMethodInfo DeviceWimaxGetNspByPathMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetNspByPath",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetNspByPath"
})
#endif
foreign import ccall "nm_device_wimax_get_nsps" nm_device_wimax_get_nsps ::
Ptr DeviceWimax ->
IO (Ptr (GPtrArray (Ptr NM.WimaxNsp.WimaxNsp)))
{-# DEPRECATED deviceWimaxGetNsps ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetNsps ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> m [NM.WimaxNsp.WimaxNsp]
deviceWimaxGetNsps :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceWimax a) =>
a -> m [WimaxNsp]
deviceWimaxGetNsps a
wimax = IO [WimaxNsp] -> m [WimaxNsp]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [WimaxNsp] -> m [WimaxNsp]) -> IO [WimaxNsp] -> m [WimaxNsp]
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceWimax
wimax' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
wimax
Ptr (GPtrArray (Ptr WimaxNsp))
result <- Ptr DeviceWimax -> IO (Ptr (GPtrArray (Ptr WimaxNsp)))
nm_device_wimax_get_nsps Ptr DeviceWimax
wimax'
Text -> Ptr (GPtrArray (Ptr WimaxNsp)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceWimaxGetNsps" Ptr (GPtrArray (Ptr WimaxNsp))
result
[Ptr WimaxNsp]
result' <- Ptr (GPtrArray (Ptr WimaxNsp)) -> IO [Ptr WimaxNsp]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr WimaxNsp))
result
[WimaxNsp]
result'' <- (Ptr WimaxNsp -> IO WimaxNsp) -> [Ptr WimaxNsp] -> IO [WimaxNsp]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr WimaxNsp -> WimaxNsp) -> Ptr WimaxNsp -> IO WimaxNsp
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr WimaxNsp -> WimaxNsp
NM.WimaxNsp.WimaxNsp) [Ptr WimaxNsp]
result'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
wimax
[WimaxNsp] -> IO [WimaxNsp]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [WimaxNsp]
result''
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetNspsMethodInfo
instance (signature ~ (m [NM.WimaxNsp.WimaxNsp]), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetNspsMethodInfo a signature where
overloadedMethod = deviceWimaxGetNsps
instance O.OverloadedMethodInfo DeviceWimaxGetNspsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetNsps",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetNsps"
})
#endif
foreign import ccall "nm_device_wimax_get_rssi" ::
Ptr DeviceWimax ->
IO Int32
{-# DEPRECATED deviceWimaxGetRssi ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetRssi ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> m Int32
a
self = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceWimax
self' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Int32
result <- Ptr DeviceWimax -> IO Int32
nm_device_wimax_get_rssi Ptr DeviceWimax
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetRssiMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetRssiMethodInfo a signature where
overloadedMethod = deviceWimaxGetRssi
instance O.OverloadedMethodInfo DeviceWimaxGetRssiMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetRssi",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetRssi"
})
#endif
foreign import ccall "nm_device_wimax_get_tx_power" nm_device_wimax_get_tx_power ::
Ptr DeviceWimax ->
IO Int32
{-# DEPRECATED deviceWimaxGetTxPower ["(Since version 1.2)","WiMAX is no longer supported."] #-}
deviceWimaxGetTxPower ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceWimax a) =>
a
-> m Int32
deviceWimaxGetTxPower :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceWimax a) =>
a -> m Int32
deviceWimaxGetTxPower a
self = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceWimax
self' <- a -> IO (Ptr DeviceWimax)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Int32
result <- Ptr DeviceWimax -> IO Int32
nm_device_wimax_get_tx_power Ptr DeviceWimax
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DeviceWimaxGetTxPowerMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDeviceWimax a) => O.OverloadedMethod DeviceWimaxGetTxPowerMethodInfo a signature where
overloadedMethod = deviceWimaxGetTxPower
instance O.OverloadedMethodInfo DeviceWimaxGetTxPowerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.DeviceWimax.deviceWimaxGetTxPower",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DeviceWimax.html#v:deviceWimaxGetTxPower"
})
#endif