{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.NM.Objects.WimaxNsp
    ( 

-- * Exported types
    WimaxNsp(..)                            ,
    IsWimaxNsp                              ,
    toWimaxNsp                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [connectionValid]("GI.NM.Objects.WimaxNsp#g:method:connectionValid"), [filterConnections]("GI.NM.Objects.WimaxNsp#g:method:filterConnections"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getClient]("GI.NM.Objects.Object#g:method:getClient"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getName]("GI.NM.Objects.WimaxNsp#g:method:getName"), [getNetworkType]("GI.NM.Objects.WimaxNsp#g:method:getNetworkType"), [getPath]("GI.NM.Objects.Object#g:method:getPath"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSignalQuality]("GI.NM.Objects.WimaxNsp#g:method:getSignalQuality").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveWimaxNspMethod                   ,
#endif

-- ** connectionValid #method:connectionValid#

#if defined(ENABLE_OVERLOADING)
    WimaxNspConnectionValidMethodInfo       ,
#endif
    wimaxNspConnectionValid                 ,


-- ** filterConnections #method:filterConnections#

#if defined(ENABLE_OVERLOADING)
    WimaxNspFilterConnectionsMethodInfo     ,
#endif
    wimaxNspFilterConnections               ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    WimaxNspGetNameMethodInfo               ,
#endif
    wimaxNspGetName                         ,


-- ** getNetworkType #method:getNetworkType#

#if defined(ENABLE_OVERLOADING)
    WimaxNspGetNetworkTypeMethodInfo        ,
#endif
    wimaxNspGetNetworkType                  ,


-- ** getSignalQuality #method:getSignalQuality#

#if defined(ENABLE_OVERLOADING)
    WimaxNspGetSignalQualityMethodInfo      ,
#endif
    wimaxNspGetSignalQuality                ,




 -- * Properties


-- ** name #attr:name#
-- | The name of the WiMAX NSP.

#if defined(ENABLE_OVERLOADING)
    WimaxNspNamePropertyInfo                ,
#endif
    getWimaxNspName                         ,
#if defined(ENABLE_OVERLOADING)
    wimaxNspName                            ,
#endif


-- ** networkType #attr:networkType#
-- | The network type of the WiMAX NSP.

#if defined(ENABLE_OVERLOADING)
    WimaxNspNetworkTypePropertyInfo         ,
#endif
    getWimaxNspNetworkType                  ,
#if defined(ENABLE_OVERLOADING)
    wimaxNspNetworkType                     ,
#endif


-- ** signalQuality #attr:signalQuality#
-- | The signal quality of the WiMAX NSP.

#if defined(ENABLE_OVERLOADING)
    WimaxNspSignalQualityPropertyInfo       ,
#endif
    getWimaxNspSignalQuality                ,
#if defined(ENABLE_OVERLOADING)
    wimaxNspSignalQuality                   ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.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.Enums as NM.Enums
import {-# SOURCE #-} qualified GI.NM.Interfaces.Connection as NM.Connection
import {-# SOURCE #-} qualified GI.NM.Objects.Object as NM.Object

#endif

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

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

foreign import ccall "nm_wimax_nsp_get_type"
    c_nm_wimax_nsp_get_type :: IO B.Types.GType

instance B.Types.TypedObject WimaxNsp where
    glibType :: IO GType
glibType = IO GType
c_nm_wimax_nsp_get_type

instance B.Types.GObject WimaxNsp

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

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

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

-- | Convert t'WimaxNsp' to and from t'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe WimaxNsp) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_nm_wimax_nsp_get_type
    gvalueSet_ :: Ptr GValue -> Maybe WimaxNsp -> IO ()
gvalueSet_ Ptr GValue
gv Maybe WimaxNsp
P.Nothing = Ptr GValue -> Ptr WimaxNsp -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr WimaxNsp
forall a. Ptr a
FP.nullPtr :: FP.Ptr WimaxNsp)
    gvalueSet_ Ptr GValue
gv (P.Just WimaxNsp
obj) = WimaxNsp -> (Ptr WimaxNsp -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr WimaxNsp
obj (Ptr GValue -> Ptr WimaxNsp -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe WimaxNsp)
gvalueGet_ Ptr GValue
gv = do
        Ptr WimaxNsp
ptr <- Ptr GValue -> IO (Ptr WimaxNsp)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr WimaxNsp)
        if Ptr WimaxNsp
ptr Ptr WimaxNsp -> Ptr WimaxNsp -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr WimaxNsp
forall a. Ptr a
FP.nullPtr
        then WimaxNsp -> Maybe WimaxNsp
forall a. a -> Maybe a
P.Just (WimaxNsp -> Maybe WimaxNsp) -> IO WimaxNsp -> IO (Maybe WimaxNsp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr WimaxNsp -> WimaxNsp) -> Ptr WimaxNsp -> IO WimaxNsp
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr WimaxNsp -> WimaxNsp
WimaxNsp Ptr WimaxNsp
ptr
        else Maybe WimaxNsp -> IO (Maybe WimaxNsp)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WimaxNsp
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveWimaxNspMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveWimaxNspMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveWimaxNspMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveWimaxNspMethod "connectionValid" o = WimaxNspConnectionValidMethodInfo
    ResolveWimaxNspMethod "filterConnections" o = WimaxNspFilterConnectionsMethodInfo
    ResolveWimaxNspMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveWimaxNspMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveWimaxNspMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveWimaxNspMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveWimaxNspMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveWimaxNspMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveWimaxNspMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveWimaxNspMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveWimaxNspMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveWimaxNspMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveWimaxNspMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveWimaxNspMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveWimaxNspMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveWimaxNspMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveWimaxNspMethod "getClient" o = NM.Object.ObjectGetClientMethodInfo
    ResolveWimaxNspMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveWimaxNspMethod "getName" o = WimaxNspGetNameMethodInfo
    ResolveWimaxNspMethod "getNetworkType" o = WimaxNspGetNetworkTypeMethodInfo
    ResolveWimaxNspMethod "getPath" o = NM.Object.ObjectGetPathMethodInfo
    ResolveWimaxNspMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveWimaxNspMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveWimaxNspMethod "getSignalQuality" o = WimaxNspGetSignalQualityMethodInfo
    ResolveWimaxNspMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveWimaxNspMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveWimaxNspMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveWimaxNspMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

#if defined(ENABLE_OVERLOADING)
data WimaxNspNamePropertyInfo
instance AttrInfo WimaxNspNamePropertyInfo where
    type AttrAllowedOps WimaxNspNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint WimaxNspNamePropertyInfo = IsWimaxNsp
    type AttrSetTypeConstraint WimaxNspNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint WimaxNspNamePropertyInfo = (~) ()
    type AttrTransferType WimaxNspNamePropertyInfo = ()
    type AttrGetType WimaxNspNamePropertyInfo = T.Text
    type AttrLabel WimaxNspNamePropertyInfo = "name"
    type AttrOrigin WimaxNspNamePropertyInfo = WimaxNsp
    attrGet = getWimaxNspName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.WimaxNsp.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-WimaxNsp.html#g:attr:name"
        })
#endif

-- VVV Prop "network-type"
   -- Type: TInterface (Name {namespace = "NM", name = "WimaxNspNetworkType"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@network-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' wimaxNsp #networkType
-- @
getWimaxNspNetworkType :: (MonadIO m, IsWimaxNsp o) => o -> m NM.Enums.WimaxNspNetworkType
getWimaxNspNetworkType :: forall (m :: * -> *) o.
(MonadIO m, IsWimaxNsp o) =>
o -> m WimaxNspNetworkType
getWimaxNspNetworkType o
obj = IO WimaxNspNetworkType -> m WimaxNspNetworkType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO WimaxNspNetworkType -> m WimaxNspNetworkType)
-> IO WimaxNspNetworkType -> m WimaxNspNetworkType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO WimaxNspNetworkType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"network-type"

#if defined(ENABLE_OVERLOADING)
data WimaxNspNetworkTypePropertyInfo
instance AttrInfo WimaxNspNetworkTypePropertyInfo where
    type AttrAllowedOps WimaxNspNetworkTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint WimaxNspNetworkTypePropertyInfo = IsWimaxNsp
    type AttrSetTypeConstraint WimaxNspNetworkTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint WimaxNspNetworkTypePropertyInfo = (~) ()
    type AttrTransferType WimaxNspNetworkTypePropertyInfo = ()
    type AttrGetType WimaxNspNetworkTypePropertyInfo = NM.Enums.WimaxNspNetworkType
    type AttrLabel WimaxNspNetworkTypePropertyInfo = "network-type"
    type AttrOrigin WimaxNspNetworkTypePropertyInfo = WimaxNsp
    attrGet = getWimaxNspNetworkType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.WimaxNsp.networkType"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-WimaxNsp.html#g:attr:networkType"
        })
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data WimaxNspSignalQualityPropertyInfo
instance AttrInfo WimaxNspSignalQualityPropertyInfo where
    type AttrAllowedOps WimaxNspSignalQualityPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint WimaxNspSignalQualityPropertyInfo = IsWimaxNsp
    type AttrSetTypeConstraint WimaxNspSignalQualityPropertyInfo = (~) ()
    type AttrTransferTypeConstraint WimaxNspSignalQualityPropertyInfo = (~) ()
    type AttrTransferType WimaxNspSignalQualityPropertyInfo = ()
    type AttrGetType WimaxNspSignalQualityPropertyInfo = Word32
    type AttrLabel WimaxNspSignalQualityPropertyInfo = "signal-quality"
    type AttrOrigin WimaxNspSignalQualityPropertyInfo = WimaxNsp
    attrGet = getWimaxNspSignalQuality
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.WimaxNsp.signalQuality"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-WimaxNsp.html#g:attr:signalQuality"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WimaxNsp
type instance O.AttributeList WimaxNsp = WimaxNspAttributeList
type WimaxNspAttributeList = ('[ '("client", NM.Object.ObjectClientPropertyInfo), '("name", WimaxNspNamePropertyInfo), '("networkType", WimaxNspNetworkTypePropertyInfo), '("path", NM.Object.ObjectPathPropertyInfo), '("signalQuality", WimaxNspSignalQualityPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
wimaxNspName :: AttrLabelProxy "name"
wimaxNspName = AttrLabelProxy

wimaxNspNetworkType :: AttrLabelProxy "networkType"
wimaxNspNetworkType = AttrLabelProxy

wimaxNspSignalQuality :: AttrLabelProxy "signalQuality"
wimaxNspSignalQuality = AttrLabelProxy

#endif

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

#endif

-- method WimaxNsp::connection_valid
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "nsp"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WimaxNsp" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an #NMWimaxNsp to validate @connection against"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "connection"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "Connection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #NMConnection to validate against @nsp"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "nm_wimax_nsp_connection_valid" nm_wimax_nsp_connection_valid :: 
    Ptr WimaxNsp ->                         -- nsp : TInterface (Name {namespace = "NM", name = "WimaxNsp"})
    Ptr NM.Connection.Connection ->         -- connection : TInterface (Name {namespace = "NM", name = "Connection"})
    IO CInt

{-# DEPRECATED wimaxNspConnectionValid ["(Since version 1.22)","WiMAX is no longer supported by NetworkManager since 1.2.0."] #-}
-- | Validates a given connection against a given WiMAX NSP to ensure that the
-- connection may be activated with that NSP.  The connection must match the
-- /@nsp@/\'s network name and other attributes.
wimaxNspConnectionValid ::
    (B.CallStack.HasCallStack, MonadIO m, IsWimaxNsp a, NM.Connection.IsConnection b) =>
    a
    -- ^ /@nsp@/: an t'GI.NM.Objects.WimaxNsp.WimaxNsp' to validate /@connection@/ against
    -> b
    -- ^ /@connection@/: an t'GI.NM.Interfaces.Connection.Connection' to validate against /@nsp@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the connection may be activated with this WiMAX NSP,
    -- 'P.False' if it cannot be.
wimaxNspConnectionValid :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWimaxNsp a, IsConnection b) =>
a -> b -> m Bool
wimaxNspConnectionValid a
nsp b
connection = 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 WimaxNsp
nsp' <- a -> IO (Ptr WimaxNsp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
nsp
    Ptr Connection
connection' <- b -> IO (Ptr Connection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
connection
    CInt
result <- Ptr WimaxNsp -> Ptr Connection -> IO CInt
nm_wimax_nsp_connection_valid Ptr WimaxNsp
nsp' Ptr Connection
connection'
    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
nsp
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
connection
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WimaxNspConnectionValidMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsWimaxNsp a, NM.Connection.IsConnection b) => O.OverloadedMethod WimaxNspConnectionValidMethodInfo a signature where
    overloadedMethod = wimaxNspConnectionValid

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


#endif

-- method WimaxNsp::filter_connections
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "nsp"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WimaxNsp" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #NMWimaxNsp to filter connections for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "connections"
--           , argType =
--               TPtrArray
--                 (TInterface Name { namespace = "NM" , name = "Connection" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #NMConnections to\nfilter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TPtrArray
--                  (TInterface Name { namespace = "NM" , name = "Connection" }))
-- throws : False
-- Skip return : False

foreign import ccall "nm_wimax_nsp_filter_connections" nm_wimax_nsp_filter_connections :: 
    Ptr WimaxNsp ->                         -- nsp : TInterface (Name {namespace = "NM", name = "WimaxNsp"})
    Ptr (GPtrArray (Ptr NM.Connection.Connection)) -> -- connections : TPtrArray (TInterface (Name {namespace = "NM", name = "Connection"}))
    IO (Ptr (GPtrArray (Ptr NM.Connection.Connection)))

{-# DEPRECATED wimaxNspFilterConnections ["(Since version 1.22)","WiMAX is no longer supported by NetworkManager since 1.2.0."] #-}
-- | Filters a given array of connections for a given t'GI.NM.Objects.WimaxNsp.WimaxNsp' object and
-- return connections which may be activated with the NSP.  Any returned
-- connections will match the /@nsp@/\'s network name and other attributes.
wimaxNspFilterConnections ::
    (B.CallStack.HasCallStack, MonadIO m, IsWimaxNsp a) =>
    a
    -- ^ /@nsp@/: an t'GI.NM.Objects.WimaxNsp.WimaxNsp' to filter connections for
    -> [NM.Connection.Connection]
    -- ^ /@connections@/: an array of @/NMConnections/@ to
    -- filter
    -> m [NM.Connection.Connection]
    -- ^ __Returns:__ an array of
    -- @/NMConnections/@ that could be activated with the given /@nsp@/.  The array should
    -- be freed with @/g_ptr_array_unref()/@ when it is no longer required.
wimaxNspFilterConnections :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWimaxNsp a) =>
a -> [Connection] -> m [Connection]
wimaxNspFilterConnections a
nsp [Connection]
connections = IO [Connection] -> m [Connection]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Connection] -> m [Connection])
-> IO [Connection] -> m [Connection]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WimaxNsp
nsp' <- a -> IO (Ptr WimaxNsp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
nsp
    [Ptr Connection]
connections' <- (Connection -> IO (Ptr Connection))
-> [Connection] -> IO [Ptr Connection]
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 Connection -> IO (Ptr Connection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [Connection]
connections
    Ptr (GPtrArray (Ptr Connection))
connections'' <- [Ptr Connection] -> IO (Ptr (GPtrArray (Ptr Connection)))
forall a. [Ptr a] -> IO (Ptr (GPtrArray (Ptr a)))
packGPtrArray [Ptr Connection]
connections'
    Ptr (GPtrArray (Ptr Connection))
result <- Ptr WimaxNsp
-> Ptr (GPtrArray (Ptr Connection))
-> IO (Ptr (GPtrArray (Ptr Connection)))
nm_wimax_nsp_filter_connections Ptr WimaxNsp
nsp' Ptr (GPtrArray (Ptr Connection))
connections''
    Text -> Ptr (GPtrArray (Ptr Connection)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wimaxNspFilterConnections" Ptr (GPtrArray (Ptr Connection))
result
    [Ptr Connection]
result' <- Ptr (GPtrArray (Ptr Connection)) -> IO [Ptr Connection]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr Connection))
result
    [Connection]
result'' <- (Ptr Connection -> IO Connection)
-> [Ptr Connection] -> IO [Connection]
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 Connection -> Connection)
-> Ptr Connection -> IO Connection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Connection -> Connection
NM.Connection.Connection) [Ptr Connection]
result'
    Ptr (GPtrArray (Ptr Connection)) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray (Ptr Connection))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
nsp
    (Connection -> IO ()) -> [Connection] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Connection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Connection]
connections
    Ptr (GPtrArray (Ptr Connection)) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray (Ptr Connection))
connections''
    [Connection] -> IO [Connection]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Connection]
result''

#if defined(ENABLE_OVERLOADING)
data WimaxNspFilterConnectionsMethodInfo
instance (signature ~ ([NM.Connection.Connection] -> m [NM.Connection.Connection]), MonadIO m, IsWimaxNsp a) => O.OverloadedMethod WimaxNspFilterConnectionsMethodInfo a signature where
    overloadedMethod = wimaxNspFilterConnections

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


#endif

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

foreign import ccall "nm_wimax_nsp_get_name" nm_wimax_nsp_get_name :: 
    Ptr WimaxNsp ->                         -- nsp : TInterface (Name {namespace = "NM", name = "WimaxNsp"})
    IO CString

{-# DEPRECATED wimaxNspGetName ["(Since version 1.22)","WiMAX is no longer supported by NetworkManager since 1.2.0."] #-}
-- | Gets the name of the wimax NSP
wimaxNspGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsWimaxNsp a) =>
    a
    -- ^ /@nsp@/: a t'GI.NM.Objects.WimaxNsp.WimaxNsp'
    -> m T.Text
    -- ^ __Returns:__ the name
wimaxNspGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWimaxNsp a) =>
a -> m Text
wimaxNspGetName a
nsp = 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 WimaxNsp
nsp' <- a -> IO (Ptr WimaxNsp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
nsp
    CString
result <- Ptr WimaxNsp -> IO CString
nm_wimax_nsp_get_name Ptr WimaxNsp
nsp'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wimaxNspGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
nsp
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WimaxNspGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWimaxNsp a) => O.OverloadedMethod WimaxNspGetNameMethodInfo a signature where
    overloadedMethod = wimaxNspGetName

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


#endif

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

foreign import ccall "nm_wimax_nsp_get_network_type" nm_wimax_nsp_get_network_type :: 
    Ptr WimaxNsp ->                         -- nsp : TInterface (Name {namespace = "NM", name = "WimaxNsp"})
    IO CUInt

{-# DEPRECATED wimaxNspGetNetworkType ["(Since version 1.22)","WiMAX is no longer supported by NetworkManager since 1.2.0."] #-}
-- | Gets the network type of the wimax NSP.
wimaxNspGetNetworkType ::
    (B.CallStack.HasCallStack, MonadIO m, IsWimaxNsp a) =>
    a
    -- ^ /@nsp@/: a t'GI.NM.Objects.WimaxNsp.WimaxNsp'
    -> m NM.Enums.WimaxNspNetworkType
    -- ^ __Returns:__ the network type
wimaxNspGetNetworkType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWimaxNsp a) =>
a -> m WimaxNspNetworkType
wimaxNspGetNetworkType a
nsp = IO WimaxNspNetworkType -> m WimaxNspNetworkType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WimaxNspNetworkType -> m WimaxNspNetworkType)
-> IO WimaxNspNetworkType -> m WimaxNspNetworkType
forall a b. (a -> b) -> a -> b
$ do
    Ptr WimaxNsp
nsp' <- a -> IO (Ptr WimaxNsp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
nsp
    CUInt
result <- Ptr WimaxNsp -> IO CUInt
nm_wimax_nsp_get_network_type Ptr WimaxNsp
nsp'
    let result' :: WimaxNspNetworkType
result' = (Int -> WimaxNspNetworkType
forall a. Enum a => Int -> a
toEnum (Int -> WimaxNspNetworkType)
-> (CUInt -> Int) -> CUInt -> WimaxNspNetworkType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
nsp
    WimaxNspNetworkType -> IO WimaxNspNetworkType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WimaxNspNetworkType
result'

#if defined(ENABLE_OVERLOADING)
data WimaxNspGetNetworkTypeMethodInfo
instance (signature ~ (m NM.Enums.WimaxNspNetworkType), MonadIO m, IsWimaxNsp a) => O.OverloadedMethod WimaxNspGetNetworkTypeMethodInfo a signature where
    overloadedMethod = wimaxNspGetNetworkType

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


#endif

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

foreign import ccall "nm_wimax_nsp_get_signal_quality" nm_wimax_nsp_get_signal_quality :: 
    Ptr WimaxNsp ->                         -- nsp : TInterface (Name {namespace = "NM", name = "WimaxNsp"})
    IO Word32

{-# DEPRECATED wimaxNspGetSignalQuality ["(Since version 1.22)","WiMAX is no longer supported by NetworkManager since 1.2.0."] #-}
-- | Gets the WPA signal quality of the wimax NSP.
wimaxNspGetSignalQuality ::
    (B.CallStack.HasCallStack, MonadIO m, IsWimaxNsp a) =>
    a
    -- ^ /@nsp@/: a t'GI.NM.Objects.WimaxNsp.WimaxNsp'
    -> m Word32
    -- ^ __Returns:__ the signal quality
wimaxNspGetSignalQuality :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWimaxNsp a) =>
a -> m Word32
wimaxNspGetSignalQuality a
nsp = 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 WimaxNsp
nsp' <- a -> IO (Ptr WimaxNsp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
nsp
    Word32
result <- Ptr WimaxNsp -> IO Word32
nm_wimax_nsp_get_signal_quality Ptr WimaxNsp
nsp'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
nsp
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data WimaxNspGetSignalQualityMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsWimaxNsp a) => O.OverloadedMethod WimaxNspGetSignalQualityMethodInfo a signature where
    overloadedMethod = wimaxNspGetSignalQuality

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


#endif