{-# 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./
-- 
-- /Since: 1.16/

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

module GI.NM.Objects.WifiP2PPeer
    ( 

-- * Exported types
    WifiP2PPeer(..)                         ,
    IsWifiP2PPeer                           ,
    toWifiP2PPeer                           ,


 -- * 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.WifiP2PPeer#g:method:connectionValid"), [filterConnections]("GI.NM.Objects.WifiP2PPeer#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"), [getFlags]("GI.NM.Objects.WifiP2PPeer#g:method:getFlags"), [getHwAddress]("GI.NM.Objects.WifiP2PPeer#g:method:getHwAddress"), [getLastSeen]("GI.NM.Objects.WifiP2PPeer#g:method:getLastSeen"), [getManufacturer]("GI.NM.Objects.WifiP2PPeer#g:method:getManufacturer"), [getModel]("GI.NM.Objects.WifiP2PPeer#g:method:getModel"), [getModelNumber]("GI.NM.Objects.WifiP2PPeer#g:method:getModelNumber"), [getName]("GI.NM.Objects.WifiP2PPeer#g:method:getName"), [getPath]("GI.NM.Objects.Object#g:method:getPath"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSerial]("GI.NM.Objects.WifiP2PPeer#g:method:getSerial"), [getStrength]("GI.NM.Objects.WifiP2PPeer#g:method:getStrength"), [getWfdIes]("GI.NM.Objects.WifiP2PPeer#g:method:getWfdIes").
-- 
-- ==== 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)
    ResolveWifiP2PPeerMethod                ,
#endif

-- ** connectionValid #method:connectionValid#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerConnectionValidMethodInfo    ,
#endif
    wifiP2PPeerConnectionValid              ,


-- ** filterConnections #method:filterConnections#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerFilterConnectionsMethodInfo  ,
#endif
    wifiP2PPeerFilterConnections            ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetFlagsMethodInfo           ,
#endif
    wifiP2PPeerGetFlags                     ,


-- ** getHwAddress #method:getHwAddress#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetHwAddressMethodInfo       ,
#endif
    wifiP2PPeerGetHwAddress                 ,


-- ** getLastSeen #method:getLastSeen#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetLastSeenMethodInfo        ,
#endif
    wifiP2PPeerGetLastSeen                  ,


-- ** getManufacturer #method:getManufacturer#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetManufacturerMethodInfo    ,
#endif
    wifiP2PPeerGetManufacturer              ,


-- ** getModel #method:getModel#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetModelMethodInfo           ,
#endif
    wifiP2PPeerGetModel                     ,


-- ** getModelNumber #method:getModelNumber#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetModelNumberMethodInfo     ,
#endif
    wifiP2PPeerGetModelNumber               ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetNameMethodInfo            ,
#endif
    wifiP2PPeerGetName                      ,


-- ** getSerial #method:getSerial#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetSerialMethodInfo          ,
#endif
    wifiP2PPeerGetSerial                    ,


-- ** getStrength #method:getStrength#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetStrengthMethodInfo        ,
#endif
    wifiP2PPeerGetStrength                  ,


-- ** getWfdIes #method:getWfdIes#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerGetWfdIesMethodInfo          ,
#endif
    wifiP2PPeerGetWfdIes                    ,




 -- * Properties


-- ** flags #attr:flags#
-- | The flags of the P2P peer.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerFlagsPropertyInfo            ,
#endif
    getWifiP2PPeerFlags                     ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerFlags                        ,
#endif


-- ** hwAddress #attr:hwAddress#
-- | The hardware address of the P2P peer.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerHwAddressPropertyInfo        ,
#endif
    getWifiP2PPeerHwAddress                 ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerHwAddress                    ,
#endif


-- ** lastSeen #attr:lastSeen#
-- | The timestamp (in CLOCK_BOOTTIME seconds) for the last time the
-- P2P peer was found.  A value of -1 means the peer has never been seen.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerLastSeenPropertyInfo         ,
#endif
    getWifiP2PPeerLastSeen                  ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerLastSeen                     ,
#endif


-- ** manufacturer #attr:manufacturer#
-- | The manufacturer of the P2P peer.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerManufacturerPropertyInfo     ,
#endif
    getWifiP2PPeerManufacturer              ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerManufacturer                 ,
#endif


-- ** model #attr:model#
-- | The model of the P2P peer.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerModelPropertyInfo            ,
#endif
    getWifiP2PPeerModel                     ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerModel                        ,
#endif


-- ** modelNumber #attr:modelNumber#
-- | The hardware address of the P2P peer.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerModelNumberPropertyInfo      ,
#endif
    getWifiP2PPeerModelNumber               ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerModelNumber                  ,
#endif


-- ** name #attr:name#
-- | The name of the P2P peer.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerNamePropertyInfo             ,
#endif
    getWifiP2PPeerName                      ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerName                         ,
#endif


-- ** serial #attr:serial#
-- | The serial number of the P2P peer.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerSerialPropertyInfo           ,
#endif
    getWifiP2PPeerSerial                    ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerSerial                       ,
#endif


-- ** strength #attr:strength#

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerStrengthPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerStrength                     ,
#endif


-- ** wfdIes #attr:wfdIes#
-- | The WFD information elements of the P2P peer.
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    WifiP2PPeerWfdIesPropertyInfo           ,
#endif
    getWifiP2PPeerWfdIes                    ,
#if defined(ENABLE_OVERLOADING)
    wifiP2PPeerWfdIes                       ,
#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.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
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.Object as NM.Object

#endif

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

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

foreign import ccall "nm_wifi_p2p_peer_get_type"
    c_nm_wifi_p2p_peer_get_type :: IO B.Types.GType

instance B.Types.TypedObject WifiP2PPeer where
    glibType :: IO GType
glibType = IO GType
c_nm_wifi_p2p_peer_get_type

instance B.Types.GObject WifiP2PPeer

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveWifiP2PPeerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveWifiP2PPeerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveWifiP2PPeerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveWifiP2PPeerMethod "connectionValid" o = WifiP2PPeerConnectionValidMethodInfo
    ResolveWifiP2PPeerMethod "filterConnections" o = WifiP2PPeerFilterConnectionsMethodInfo
    ResolveWifiP2PPeerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveWifiP2PPeerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveWifiP2PPeerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveWifiP2PPeerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveWifiP2PPeerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveWifiP2PPeerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveWifiP2PPeerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveWifiP2PPeerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveWifiP2PPeerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveWifiP2PPeerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveWifiP2PPeerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveWifiP2PPeerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveWifiP2PPeerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveWifiP2PPeerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveWifiP2PPeerMethod "getClient" o = NM.Object.ObjectGetClientMethodInfo
    ResolveWifiP2PPeerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveWifiP2PPeerMethod "getFlags" o = WifiP2PPeerGetFlagsMethodInfo
    ResolveWifiP2PPeerMethod "getHwAddress" o = WifiP2PPeerGetHwAddressMethodInfo
    ResolveWifiP2PPeerMethod "getLastSeen" o = WifiP2PPeerGetLastSeenMethodInfo
    ResolveWifiP2PPeerMethod "getManufacturer" o = WifiP2PPeerGetManufacturerMethodInfo
    ResolveWifiP2PPeerMethod "getModel" o = WifiP2PPeerGetModelMethodInfo
    ResolveWifiP2PPeerMethod "getModelNumber" o = WifiP2PPeerGetModelNumberMethodInfo
    ResolveWifiP2PPeerMethod "getName" o = WifiP2PPeerGetNameMethodInfo
    ResolveWifiP2PPeerMethod "getPath" o = NM.Object.ObjectGetPathMethodInfo
    ResolveWifiP2PPeerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveWifiP2PPeerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveWifiP2PPeerMethod "getSerial" o = WifiP2PPeerGetSerialMethodInfo
    ResolveWifiP2PPeerMethod "getStrength" o = WifiP2PPeerGetStrengthMethodInfo
    ResolveWifiP2PPeerMethod "getWfdIes" o = WifiP2PPeerGetWfdIesMethodInfo
    ResolveWifiP2PPeerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveWifiP2PPeerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveWifiP2PPeerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveWifiP2PPeerMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

-- | Get the value of the “@flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' wifiP2PPeer #flags
-- @
getWifiP2PPeerFlags :: (MonadIO m, IsWifiP2PPeer o) => o -> m [NM.Flags.NM80211ApFlags]
getWifiP2PPeerFlags :: forall (m :: * -> *) o.
(MonadIO m, IsWifiP2PPeer o) =>
o -> m [NM80211ApFlags]
getWifiP2PPeerFlags o
obj = IO [NM80211ApFlags] -> m [NM80211ApFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [NM80211ApFlags] -> m [NM80211ApFlags])
-> IO [NM80211ApFlags] -> m [NM80211ApFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [NM80211ApFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"flags"

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

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

-- | Get the value of the “@hw-address@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' wifiP2PPeer #hwAddress
-- @
getWifiP2PPeerHwAddress :: (MonadIO m, IsWifiP2PPeer o) => o -> m T.Text
getWifiP2PPeerHwAddress :: forall (m :: * -> *) o. (MonadIO m, IsWifiP2PPeer o) => o -> m Text
getWifiP2PPeerHwAddress 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
"getWifiP2PPeerHwAddress" (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 WifiP2PPeerHwAddressPropertyInfo
instance AttrInfo WifiP2PPeerHwAddressPropertyInfo where
    type AttrAllowedOps WifiP2PPeerHwAddressPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint WifiP2PPeerHwAddressPropertyInfo = IsWifiP2PPeer
    type AttrSetTypeConstraint WifiP2PPeerHwAddressPropertyInfo = (~) ()
    type AttrTransferTypeConstraint WifiP2PPeerHwAddressPropertyInfo = (~) ()
    type AttrTransferType WifiP2PPeerHwAddressPropertyInfo = ()
    type AttrGetType WifiP2PPeerHwAddressPropertyInfo = T.Text
    type AttrLabel WifiP2PPeerHwAddressPropertyInfo = "hw-address"
    type AttrOrigin WifiP2PPeerHwAddressPropertyInfo = WifiP2PPeer
    attrGet = getWifiP2PPeerHwAddress
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.WifiP2PPeer.hwAddress"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-WifiP2PPeer.html#g:attr:hwAddress"
        })
#endif

-- VVV Prop "last-seen"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerLastSeenPropertyInfo
instance AttrInfo WifiP2PPeerLastSeenPropertyInfo where
    type AttrAllowedOps WifiP2PPeerLastSeenPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint WifiP2PPeerLastSeenPropertyInfo = IsWifiP2PPeer
    type AttrSetTypeConstraint WifiP2PPeerLastSeenPropertyInfo = (~) ()
    type AttrTransferTypeConstraint WifiP2PPeerLastSeenPropertyInfo = (~) ()
    type AttrTransferType WifiP2PPeerLastSeenPropertyInfo = ()
    type AttrGetType WifiP2PPeerLastSeenPropertyInfo = Int32
    type AttrLabel WifiP2PPeerLastSeenPropertyInfo = "last-seen"
    type AttrOrigin WifiP2PPeerLastSeenPropertyInfo = WifiP2PPeer
    attrGet = getWifiP2PPeerLastSeen
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.WifiP2PPeer.lastSeen"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-WifiP2PPeer.html#g:attr:lastSeen"
        })
#endif

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

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

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

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerModelNumberPropertyInfo
instance AttrInfo WifiP2PPeerModelNumberPropertyInfo where
    type AttrAllowedOps WifiP2PPeerModelNumberPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint WifiP2PPeerModelNumberPropertyInfo = IsWifiP2PPeer
    type AttrSetTypeConstraint WifiP2PPeerModelNumberPropertyInfo = (~) ()
    type AttrTransferTypeConstraint WifiP2PPeerModelNumberPropertyInfo = (~) ()
    type AttrTransferType WifiP2PPeerModelNumberPropertyInfo = ()
    type AttrGetType WifiP2PPeerModelNumberPropertyInfo = T.Text
    type AttrLabel WifiP2PPeerModelNumberPropertyInfo = "model-number"
    type AttrOrigin WifiP2PPeerModelNumberPropertyInfo = WifiP2PPeer
    attrGet = getWifiP2PPeerModelNumber
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.WifiP2PPeer.modelNumber"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-WifiP2PPeer.html#g:attr:modelNumber"
        })
#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' wifiP2PPeer #name
-- @
getWifiP2PPeerName :: (MonadIO m, IsWifiP2PPeer o) => o -> m T.Text
getWifiP2PPeerName :: forall (m :: * -> *) o. (MonadIO m, IsWifiP2PPeer o) => o -> m Text
getWifiP2PPeerName 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
"getWifiP2PPeerName" (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 WifiP2PPeerNamePropertyInfo
instance AttrInfo WifiP2PPeerNamePropertyInfo where
    type AttrAllowedOps WifiP2PPeerNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint WifiP2PPeerNamePropertyInfo = IsWifiP2PPeer
    type AttrSetTypeConstraint WifiP2PPeerNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint WifiP2PPeerNamePropertyInfo = (~) ()
    type AttrTransferType WifiP2PPeerNamePropertyInfo = ()
    type AttrGetType WifiP2PPeerNamePropertyInfo = T.Text
    type AttrLabel WifiP2PPeerNamePropertyInfo = "name"
    type AttrOrigin WifiP2PPeerNamePropertyInfo = WifiP2PPeer
    attrGet = getWifiP2PPeerName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.WifiP2PPeer.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-WifiP2PPeer.html#g:attr:name"
        })
#endif

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

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

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

-- XXX Generation of property "strength" of object "WifiP2PPeer" failed.
-- Not implemented: Don't know how to handle properties of type TBasicType TUInt8
#if defined(ENABLE_OVERLOADING)
-- XXX Placeholder
data WifiP2PPeerStrengthPropertyInfo
instance AttrInfo WifiP2PPeerStrengthPropertyInfo where
    type AttrAllowedOps WifiP2PPeerStrengthPropertyInfo = '[]
    type AttrSetTypeConstraint WifiP2PPeerStrengthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint WifiP2PPeerStrengthPropertyInfo = (~) ()
    type AttrTransferType WifiP2PPeerStrengthPropertyInfo = ()
    type AttrBaseTypeConstraint WifiP2PPeerStrengthPropertyInfo = (~) ()
    type AttrGetType WifiP2PPeerStrengthPropertyInfo = ()
    type AttrLabel WifiP2PPeerStrengthPropertyInfo = ""
    type AttrOrigin WifiP2PPeerStrengthPropertyInfo = WifiP2PPeer
    attrGet = undefined
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
#endif

-- VVV Prop "wfd-ies"
   -- Type: TInterface (Name {namespace = "GLib", name = "Bytes"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@wfd-ies@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' wifiP2PPeer #wfdIes
-- @
getWifiP2PPeerWfdIes :: (MonadIO m, IsWifiP2PPeer o) => o -> m GLib.Bytes.Bytes
getWifiP2PPeerWfdIes :: forall (m :: * -> *) o.
(MonadIO m, IsWifiP2PPeer o) =>
o -> m Bytes
getWifiP2PPeerWfdIes o
obj = IO Bytes -> m Bytes
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Bytes) -> IO Bytes
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getWifiP2PPeerWfdIes" (IO (Maybe Bytes) -> IO Bytes) -> IO (Maybe Bytes) -> IO Bytes
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Bytes -> Bytes) -> IO (Maybe Bytes)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"wfd-ies" ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WifiP2PPeer
type instance O.AttributeList WifiP2PPeer = WifiP2PPeerAttributeList
type WifiP2PPeerAttributeList = ('[ '("client", NM.Object.ObjectClientPropertyInfo), '("flags", WifiP2PPeerFlagsPropertyInfo), '("hwAddress", WifiP2PPeerHwAddressPropertyInfo), '("lastSeen", WifiP2PPeerLastSeenPropertyInfo), '("manufacturer", WifiP2PPeerManufacturerPropertyInfo), '("model", WifiP2PPeerModelPropertyInfo), '("modelNumber", WifiP2PPeerModelNumberPropertyInfo), '("name", WifiP2PPeerNamePropertyInfo), '("path", NM.Object.ObjectPathPropertyInfo), '("serial", WifiP2PPeerSerialPropertyInfo), '("strength", WifiP2PPeerStrengthPropertyInfo), '("wfdIes", WifiP2PPeerWfdIesPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
wifiP2PPeerFlags :: AttrLabelProxy "flags"
wifiP2PPeerFlags = AttrLabelProxy

wifiP2PPeerHwAddress :: AttrLabelProxy "hwAddress"
wifiP2PPeerHwAddress = AttrLabelProxy

wifiP2PPeerLastSeen :: AttrLabelProxy "lastSeen"
wifiP2PPeerLastSeen = AttrLabelProxy

wifiP2PPeerManufacturer :: AttrLabelProxy "manufacturer"
wifiP2PPeerManufacturer = AttrLabelProxy

wifiP2PPeerModel :: AttrLabelProxy "model"
wifiP2PPeerModel = AttrLabelProxy

wifiP2PPeerModelNumber :: AttrLabelProxy "modelNumber"
wifiP2PPeerModelNumber = AttrLabelProxy

wifiP2PPeerName :: AttrLabelProxy "name"
wifiP2PPeerName = AttrLabelProxy

wifiP2PPeerSerial :: AttrLabelProxy "serial"
wifiP2PPeerSerial = AttrLabelProxy

wifiP2PPeerStrength :: AttrLabelProxy "strength"
wifiP2PPeerStrength = AttrLabelProxy

wifiP2PPeerWfdIes :: AttrLabelProxy "wfdIes"
wifiP2PPeerWfdIes = AttrLabelProxy

#endif

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

#endif

-- method WifiP2PPeer::connection_valid
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WifiP2PPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an #NMWifiP2PPeer 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 @peer"
--                 , 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_wifi_p2p_peer_connection_valid" nm_wifi_p2p_peer_connection_valid :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    Ptr NM.Connection.Connection ->         -- connection : TInterface (Name {namespace = "NM", name = "Connection"})
    IO CInt

-- | Validates a given connection against a given Wi-Fi P2P peer to ensure that
-- the connection may be activated with that peer. The connection must match the
-- /@peer@/\'s address and in the future possibly other attributes.
-- 
-- /Since: 1.16/
wifiP2PPeerConnectionValid ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a, NM.Connection.IsConnection b) =>
    a
    -- ^ /@peer@/: an t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer' to validate /@connection@/ against
    -> b
    -- ^ /@connection@/: an t'GI.NM.Interfaces.Connection.Connection' to validate against /@peer@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the connection may be activated with this Wi-Fi P2P Peer,
    -- 'P.False' if it cannot be.
wifiP2PPeerConnectionValid :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWifiP2PPeer a, IsConnection b) =>
a -> b -> m Bool
wifiP2PPeerConnectionValid a
peer 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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    Ptr Connection
connection' <- b -> IO (Ptr Connection)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
connection
    CInt
result <- Ptr WifiP2PPeer -> Ptr Connection -> IO CInt
nm_wifi_p2p_peer_connection_valid Ptr WifiP2PPeer
peer' 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
peer
    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 WifiP2PPeerConnectionValidMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsWifiP2PPeer a, NM.Connection.IsConnection b) => O.OverloadedMethod WifiP2PPeerConnectionValidMethodInfo a signature where
    overloadedMethod = wifiP2PPeerConnectionValid

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


#endif

-- method WifiP2PPeer::filter_connections
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WifiP2PPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #NMWifiP2PPeer 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_wifi_p2p_peer_filter_connections" nm_wifi_p2p_peer_filter_connections :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    Ptr (GPtrArray (Ptr NM.Connection.Connection)) -> -- connections : TPtrArray (TInterface (Name {namespace = "NM", name = "Connection"}))
    IO (Ptr (GPtrArray (Ptr NM.Connection.Connection)))

-- | Filters a given array of connections for a given t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer' object and
-- returns connections which may be activated with the P2P peer.  Any
-- returned connections will match the /@peers@/\'s HW address and in the future
-- possibly other attributes.
-- 
-- To obtain the list of connections that are compatible with this P2P peer,
-- use 'GI.NM.Objects.Client.clientGetConnections' and then filter the returned list for a given
-- t'GI.NM.Objects.Device.Device' using 'GI.NM.Objects.Device.deviceFilterConnections' and finally filter that list
-- with this function.
-- 
-- /Since: 1.16/
wifiP2PPeerFilterConnections ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: an t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer' 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 /@peer@/. The array should
    -- be freed with @/g_ptr_array_unref()/@ when it is no longer required.
wifiP2PPeerFilterConnections :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> [Connection] -> m [Connection]
wifiP2PPeerFilterConnections a
peer [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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    [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 WifiP2PPeer
-> Ptr (GPtrArray (Ptr Connection))
-> IO (Ptr (GPtrArray (Ptr Connection)))
nm_wifi_p2p_peer_filter_connections Ptr WifiP2PPeer
peer' Ptr (GPtrArray (Ptr Connection))
connections''
    Text -> Ptr (GPtrArray (Ptr Connection)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wifiP2PPeerFilterConnections" 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
newObject 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
peer
    (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 WifiP2PPeerFilterConnectionsMethodInfo
instance (signature ~ ([NM.Connection.Connection] -> m [NM.Connection.Connection]), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerFilterConnectionsMethodInfo a signature where
    overloadedMethod = wifiP2PPeerFilterConnections

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


#endif

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

foreign import ccall "nm_wifi_p2p_peer_get_flags" nm_wifi_p2p_peer_get_flags :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO CUInt

-- | Gets the flags of the P2P peer.
-- 
-- /Since: 1.16/
wifiP2PPeerGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m [NM.Flags.NM80211ApFlags]
    -- ^ __Returns:__ the flags
wifiP2PPeerGetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m [NM80211ApFlags]
wifiP2PPeerGetFlags a
peer = IO [NM80211ApFlags] -> m [NM80211ApFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [NM80211ApFlags] -> m [NM80211ApFlags])
-> IO [NM80211ApFlags] -> m [NM80211ApFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    CUInt
result <- Ptr WifiP2PPeer -> IO CUInt
nm_wifi_p2p_peer_get_flags Ptr WifiP2PPeer
peer'
    let result' :: [NM80211ApFlags]
result' = CUInt -> [NM80211ApFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    [NM80211ApFlags] -> IO [NM80211ApFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [NM80211ApFlags]
result'

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetFlagsMethodInfo
instance (signature ~ (m [NM.Flags.NM80211ApFlags]), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetFlagsMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetFlags

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


#endif

-- method WifiP2PPeer::get_hw_address
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WifiP2PPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMWifiP2PPeer" , 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_wifi_p2p_peer_get_hw_address" nm_wifi_p2p_peer_get_hw_address :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO CString

-- | Gets the hardware address of the P2P peer.
-- 
-- /Since: 1.16/
wifiP2PPeerGetHwAddress ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m T.Text
    -- ^ __Returns:__ the hardware address
wifiP2PPeerGetHwAddress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Text
wifiP2PPeerGetHwAddress a
peer = 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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    CString
result <- Ptr WifiP2PPeer -> IO CString
nm_wifi_p2p_peer_get_hw_address Ptr WifiP2PPeer
peer'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wifiP2PPeerGetHwAddress" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetHwAddressMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetHwAddressMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetHwAddress

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


#endif

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

foreign import ccall "nm_wifi_p2p_peer_get_last_seen" nm_wifi_p2p_peer_get_last_seen :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO Int32

-- | Returns the timestamp (in CLOCK_BOOTTIME seconds) for the last time the
-- P2P peer was seen.  A value of -1 means the P2P peer has never been seen.
-- 
-- /Since: 1.16/
wifiP2PPeerGetLastSeen ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m Int32
    -- ^ __Returns:__ the last seen time in seconds
wifiP2PPeerGetLastSeen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Int32
wifiP2PPeerGetLastSeen a
peer = 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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    Int32
result <- Ptr WifiP2PPeer -> IO Int32
nm_wifi_p2p_peer_get_last_seen Ptr WifiP2PPeer
peer'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetLastSeenMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetLastSeenMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetLastSeen

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


#endif

-- method WifiP2PPeer::get_manufacturer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WifiP2PPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMWifiP2PPeer" , 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_wifi_p2p_peer_get_manufacturer" nm_wifi_p2p_peer_get_manufacturer :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO CString

-- | Gets the manufacturer of the P2P peer.
-- 
-- /Since: 1.16/
wifiP2PPeerGetManufacturer ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m T.Text
    -- ^ __Returns:__ the manufacturer
wifiP2PPeerGetManufacturer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Text
wifiP2PPeerGetManufacturer a
peer = 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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    CString
result <- Ptr WifiP2PPeer -> IO CString
nm_wifi_p2p_peer_get_manufacturer Ptr WifiP2PPeer
peer'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wifiP2PPeerGetManufacturer" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetManufacturerMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetManufacturerMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetManufacturer

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


#endif

-- method WifiP2PPeer::get_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WifiP2PPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMWifiP2PPeer" , 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_wifi_p2p_peer_get_model" nm_wifi_p2p_peer_get_model :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO CString

-- | Gets the model of the P2P peer.
-- 
-- /Since: 1.16/
wifiP2PPeerGetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m T.Text
    -- ^ __Returns:__ the model
wifiP2PPeerGetModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Text
wifiP2PPeerGetModel a
peer = 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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    CString
result <- Ptr WifiP2PPeer -> IO CString
nm_wifi_p2p_peer_get_model Ptr WifiP2PPeer
peer'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wifiP2PPeerGetModel" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetModelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetModelMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetModel

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


#endif

-- method WifiP2PPeer::get_model_number
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WifiP2PPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMWifiP2PPeer" , 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_wifi_p2p_peer_get_model_number" nm_wifi_p2p_peer_get_model_number :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO CString

-- | Gets the model number of the P2P peer.
-- 
-- /Since: 1.16/
wifiP2PPeerGetModelNumber ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m T.Text
    -- ^ __Returns:__ the model number
wifiP2PPeerGetModelNumber :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Text
wifiP2PPeerGetModelNumber a
peer = 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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    CString
result <- Ptr WifiP2PPeer -> IO CString
nm_wifi_p2p_peer_get_model_number Ptr WifiP2PPeer
peer'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wifiP2PPeerGetModelNumber" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetModelNumberMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetModelNumberMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetModelNumber

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


#endif

-- method WifiP2PPeer::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WifiP2PPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMWifiP2PPeer" , 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_wifi_p2p_peer_get_name" nm_wifi_p2p_peer_get_name :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO CString

-- | Gets the name of the P2P peer.
-- 
-- /Since: 1.16/
wifiP2PPeerGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m T.Text
    -- ^ __Returns:__ the name
wifiP2PPeerGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Text
wifiP2PPeerGetName a
peer = 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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    CString
result <- Ptr WifiP2PPeer -> IO CString
nm_wifi_p2p_peer_get_name Ptr WifiP2PPeer
peer'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wifiP2PPeerGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetNameMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetName

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


#endif

-- method WifiP2PPeer::get_serial
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "peer"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "WifiP2PPeer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMWifiP2PPeer" , 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_wifi_p2p_peer_get_serial" nm_wifi_p2p_peer_get_serial :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO CString

-- | Gets the serial number of the P2P peer.
-- 
-- /Since: 1.16/
wifiP2PPeerGetSerial ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m T.Text
    -- ^ __Returns:__ the serial number
wifiP2PPeerGetSerial :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Text
wifiP2PPeerGetSerial a
peer = 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 WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    CString
result <- Ptr WifiP2PPeer -> IO CString
nm_wifi_p2p_peer_get_serial Ptr WifiP2PPeer
peer'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wifiP2PPeerGetSerial" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetSerialMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetSerialMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetSerial

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


#endif

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

foreign import ccall "nm_wifi_p2p_peer_get_strength" nm_wifi_p2p_peer_get_strength :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO Word8

-- | Gets the current signal strength of the P2P peer as a percentage.
-- 
-- /Since: 1.16/
wifiP2PPeerGetStrength ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m Word8
    -- ^ __Returns:__ the signal strength (0 to 100)
wifiP2PPeerGetStrength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Word8
wifiP2PPeerGetStrength a
peer = IO Word8 -> m Word8
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
    Ptr WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    Word8
result <- Ptr WifiP2PPeer -> IO Word8
nm_wifi_p2p_peer_get_strength Ptr WifiP2PPeer
peer'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Word8 -> IO Word8
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetStrengthMethodInfo
instance (signature ~ (m Word8), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetStrengthMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetStrength

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


#endif

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

foreign import ccall "nm_wifi_p2p_peer_get_wfd_ies" nm_wifi_p2p_peer_get_wfd_ies :: 
    Ptr WifiP2PPeer ->                      -- peer : TInterface (Name {namespace = "NM", name = "WifiP2PPeer"})
    IO (Ptr GLib.Bytes.Bytes)

-- | Gets the WFD information elements of the P2P peer.
-- 
-- /Since: 1.16/
wifiP2PPeerGetWfdIes ::
    (B.CallStack.HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
    a
    -- ^ /@peer@/: a t'GI.NM.Objects.WifiP2PPeer.WifiP2PPeer'
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ the t'GI.GLib.Structs.Bytes.Bytes' containing the WFD IEs, or 'P.Nothing'.
wifiP2PPeerGetWfdIes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWifiP2PPeer a) =>
a -> m Bytes
wifiP2PPeerGetWfdIes a
peer = IO Bytes -> m Bytes
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
    Ptr WifiP2PPeer
peer' <- a -> IO (Ptr WifiP2PPeer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
peer
    Ptr Bytes
result <- Ptr WifiP2PPeer -> IO (Ptr Bytes)
nm_wifi_p2p_peer_get_wfd_ies Ptr WifiP2PPeer
peer'
    Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"wifiP2PPeerGetWfdIes" Ptr Bytes
result
    Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
peer
    Bytes -> IO Bytes
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'

#if defined(ENABLE_OVERLOADING)
data WifiP2PPeerGetWfdIesMethodInfo
instance (signature ~ (m GLib.Bytes.Bytes), MonadIO m, IsWifiP2PPeer a) => O.OverloadedMethod WifiP2PPeerGetWfdIesMethodInfo a signature where
    overloadedMethod = wifiP2PPeerGetWfdIes

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


#endif