{-# 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.IPConfig
    ( 

-- * Exported types
    IPConfig(..)                            ,
    IsIPConfig                              ,
    toIPConfig                              ,


 -- * 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"), [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
-- [getAddresses]("GI.NM.Objects.IPConfig#g:method:getAddresses"), [getClient]("GI.NM.Objects.Object#g:method:getClient"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDomains]("GI.NM.Objects.IPConfig#g:method:getDomains"), [getFamily]("GI.NM.Objects.IPConfig#g:method:getFamily"), [getGateway]("GI.NM.Objects.IPConfig#g:method:getGateway"), [getNameservers]("GI.NM.Objects.IPConfig#g:method:getNameservers"), [getPath]("GI.NM.Objects.Object#g:method:getPath"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRoutes]("GI.NM.Objects.IPConfig#g:method:getRoutes"), [getSearches]("GI.NM.Objects.IPConfig#g:method:getSearches"), [getWinsServers]("GI.NM.Objects.IPConfig#g:method:getWinsServers").
-- 
-- ==== 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)
    ResolveIPConfigMethod                   ,
#endif

-- ** getAddresses #method:getAddresses#

#if defined(ENABLE_OVERLOADING)
    IPConfigGetAddressesMethodInfo          ,
#endif
    iPConfigGetAddresses                    ,


-- ** getDomains #method:getDomains#

#if defined(ENABLE_OVERLOADING)
    IPConfigGetDomainsMethodInfo            ,
#endif
    iPConfigGetDomains                      ,


-- ** getFamily #method:getFamily#

#if defined(ENABLE_OVERLOADING)
    IPConfigGetFamilyMethodInfo             ,
#endif
    iPConfigGetFamily                       ,


-- ** getGateway #method:getGateway#

#if defined(ENABLE_OVERLOADING)
    IPConfigGetGatewayMethodInfo            ,
#endif
    iPConfigGetGateway                      ,


-- ** getNameservers #method:getNameservers#

#if defined(ENABLE_OVERLOADING)
    IPConfigGetNameserversMethodInfo        ,
#endif
    iPConfigGetNameservers                  ,


-- ** getRoutes #method:getRoutes#

#if defined(ENABLE_OVERLOADING)
    IPConfigGetRoutesMethodInfo             ,
#endif
    iPConfigGetRoutes                       ,


-- ** getSearches #method:getSearches#

#if defined(ENABLE_OVERLOADING)
    IPConfigGetSearchesMethodInfo           ,
#endif
    iPConfigGetSearches                     ,


-- ** getWinsServers #method:getWinsServers#

#if defined(ENABLE_OVERLOADING)
    IPConfigGetWinsServersMethodInfo        ,
#endif
    iPConfigGetWinsServers                  ,




 -- * Properties


-- ** addresses #attr:addresses#

#if defined(ENABLE_OVERLOADING)
    IPConfigAddressesPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    iPConfigAddresses                       ,
#endif


-- ** domains #attr:domains#
-- | The array containing domain strings of the configuration.

#if defined(ENABLE_OVERLOADING)
    IPConfigDomainsPropertyInfo             ,
#endif
    getIPConfigDomains                      ,
#if defined(ENABLE_OVERLOADING)
    iPConfigDomains                         ,
#endif


-- ** family #attr:family#
-- | The IP address family of the configuration; either
-- \<literal>AF_INET\<\/literal> or \<literal>AF_INET6\<\/literal>.

#if defined(ENABLE_OVERLOADING)
    IPConfigFamilyPropertyInfo              ,
#endif
    getIPConfigFamily                       ,
#if defined(ENABLE_OVERLOADING)
    iPConfigFamily                          ,
#endif


-- ** gateway #attr:gateway#
-- | The IP gateway address of the configuration as string.

#if defined(ENABLE_OVERLOADING)
    IPConfigGatewayPropertyInfo             ,
#endif
    getIPConfigGateway                      ,
#if defined(ENABLE_OVERLOADING)
    iPConfigGateway                         ,
#endif


-- ** nameservers #attr:nameservers#
-- | The array containing name server IP addresses of the configuration.

#if defined(ENABLE_OVERLOADING)
    IPConfigNameserversPropertyInfo         ,
#endif
    getIPConfigNameservers                  ,
#if defined(ENABLE_OVERLOADING)
    iPConfigNameservers                     ,
#endif


-- ** routes #attr:routes#

#if defined(ENABLE_OVERLOADING)
    IPConfigRoutesPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    iPConfigRoutes                          ,
#endif


-- ** searches #attr:searches#
-- | The array containing DNS search strings of the configuration.

#if defined(ENABLE_OVERLOADING)
    IPConfigSearchesPropertyInfo            ,
#endif
    getIPConfigSearches                     ,
#if defined(ENABLE_OVERLOADING)
    iPConfigSearches                        ,
#endif


-- ** winsServers #attr:winsServers#
-- | The array containing WINS server IP addresses of the configuration.
-- (This will always be empty for IPv6 configurations.)

#if defined(ENABLE_OVERLOADING)
    IPConfigWinsServersPropertyInfo         ,
#endif
    getIPConfigWinsServers                  ,
#if defined(ENABLE_OVERLOADING)
    iPConfigWinsServers                     ,
#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.Object as NM.Object
import {-# SOURCE #-} qualified GI.NM.Objects.RemoteConnection as NM.RemoteConnection
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
import {-# SOURCE #-} qualified GI.NM.Objects.Setting8021x as NM.Setting8021x
import {-# SOURCE #-} qualified GI.NM.Objects.SettingAdsl as NM.SettingAdsl
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBluetooth as NM.SettingBluetooth
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBond as NM.SettingBond
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridge as NM.SettingBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridgePort as NM.SettingBridgePort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingCdma as NM.SettingCdma
import {-# SOURCE #-} qualified GI.NM.Objects.SettingConnection as NM.SettingConnection
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDcb as NM.SettingDcb
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDummy as NM.SettingDummy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGeneric as NM.SettingGeneric
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGsm as NM.SettingGsm
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP4Config as NM.SettingIP4Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP6Config as NM.SettingIP6Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPConfig as NM.SettingIPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPTunnel as NM.SettingIPTunnel
import {-# SOURCE #-} qualified GI.NM.Objects.SettingInfiniband as NM.SettingInfiniband
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacsec as NM.SettingMacsec
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacvlan as NM.SettingMacvlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOlpcMesh as NM.SettingOlpcMesh
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsBridge as NM.SettingOvsBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsInterface as NM.SettingOvsInterface
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPatch as NM.SettingOvsPatch
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPort as NM.SettingOvsPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPpp as NM.SettingPpp
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPppoe as NM.SettingPppoe
import {-# SOURCE #-} qualified GI.NM.Objects.SettingProxy as NM.SettingProxy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingSerial as NM.SettingSerial
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTCConfig as NM.SettingTCConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeam as NM.SettingTeam
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeamPort as NM.SettingTeamPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTun as NM.SettingTun
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVlan as NM.SettingVlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVpn as NM.SettingVpn
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVxlan as NM.SettingVxlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWimax as NM.SettingWimax
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWired as NM.SettingWired
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWireless as NM.SettingWireless
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWirelessSecurity as NM.SettingWirelessSecurity
import {-# SOURCE #-} qualified GI.NM.Structs.BridgeVlan as NM.BridgeVlan
import {-# SOURCE #-} qualified GI.NM.Structs.DnsEntry as NM.DnsEntry
import {-# SOURCE #-} qualified GI.NM.Structs.IPAddress as NM.IPAddress
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoute as NM.IPRoute
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoutingRule as NM.IPRoutingRule
import {-# SOURCE #-} qualified GI.NM.Structs.LldpNeighbor as NM.LldpNeighbor
import {-# SOURCE #-} qualified GI.NM.Structs.Range as NM.Range
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.NM.Objects.Object as NM.Object
import {-# SOURCE #-} qualified GI.NM.Structs.IPAddress as NM.IPAddress
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoute as NM.IPRoute

#endif

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

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

foreign import ccall "nm_ip_config_get_type"
    c_nm_ip_config_get_type :: IO B.Types.GType

instance B.Types.TypedObject IPConfig where
    glibType :: IO GType
glibType = IO GType
c_nm_ip_config_get_type

instance B.Types.GObject IPConfig

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveIPConfigMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveIPConfigMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveIPConfigMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveIPConfigMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveIPConfigMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveIPConfigMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveIPConfigMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveIPConfigMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveIPConfigMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveIPConfigMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveIPConfigMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveIPConfigMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveIPConfigMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveIPConfigMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveIPConfigMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveIPConfigMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveIPConfigMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveIPConfigMethod "getAddresses" o = IPConfigGetAddressesMethodInfo
    ResolveIPConfigMethod "getClient" o = NM.Object.ObjectGetClientMethodInfo
    ResolveIPConfigMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveIPConfigMethod "getDomains" o = IPConfigGetDomainsMethodInfo
    ResolveIPConfigMethod "getFamily" o = IPConfigGetFamilyMethodInfo
    ResolveIPConfigMethod "getGateway" o = IPConfigGetGatewayMethodInfo
    ResolveIPConfigMethod "getNameservers" o = IPConfigGetNameserversMethodInfo
    ResolveIPConfigMethod "getPath" o = NM.Object.ObjectGetPathMethodInfo
    ResolveIPConfigMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveIPConfigMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveIPConfigMethod "getRoutes" o = IPConfigGetRoutesMethodInfo
    ResolveIPConfigMethod "getSearches" o = IPConfigGetSearchesMethodInfo
    ResolveIPConfigMethod "getWinsServers" o = IPConfigGetWinsServersMethodInfo
    ResolveIPConfigMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveIPConfigMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveIPConfigMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveIPConfigMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

-- VVV Prop "domains"
   -- Type: TCArray True (-1) (-1) (TBasicType TUTF8)
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

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

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

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

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

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

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

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

-- VVV Prop "nameservers"
   -- Type: TCArray True (-1) (-1) (TBasicType TUTF8)
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

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

-- XXX Generation of property "routes" of object "IPConfig" failed.
-- Not implemented: Don't know how to handle properties of type TPtrArray (TInterface (Name {namespace = "NM", name = "IPRoute"}))
#if defined(ENABLE_OVERLOADING)
-- XXX Placeholder
data IPConfigRoutesPropertyInfo
instance AttrInfo IPConfigRoutesPropertyInfo where
    type AttrAllowedOps IPConfigRoutesPropertyInfo = '[]
    type AttrSetTypeConstraint IPConfigRoutesPropertyInfo = (~) ()
    type AttrTransferTypeConstraint IPConfigRoutesPropertyInfo = (~) ()
    type AttrTransferType IPConfigRoutesPropertyInfo = ()
    type AttrBaseTypeConstraint IPConfigRoutesPropertyInfo = (~) ()
    type AttrGetType IPConfigRoutesPropertyInfo = ()
    type AttrLabel IPConfigRoutesPropertyInfo = ""
    type AttrOrigin IPConfigRoutesPropertyInfo = IPConfig
    attrGet = undefined
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
#endif

-- VVV Prop "searches"
   -- Type: TCArray True (-1) (-1) (TBasicType TUTF8)
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

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

-- VVV Prop "wins-servers"
   -- Type: TCArray True (-1) (-1) (TBasicType TUTF8)
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@wins-servers@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' iPConfig #winsServers
-- @
getIPConfigWinsServers :: (MonadIO m, IsIPConfig o) => o -> m [T.Text]
getIPConfigWinsServers :: forall (m :: * -> *) o. (MonadIO m, IsIPConfig o) => o -> m [Text]
getIPConfigWinsServers 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
"getIPConfigWinsServers" (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.getObjectPropertyStringArray o
obj String
"wins-servers"

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IPConfig
type instance O.AttributeList IPConfig = IPConfigAttributeList
type IPConfigAttributeList = ('[ '("addresses", IPConfigAddressesPropertyInfo), '("client", NM.Object.ObjectClientPropertyInfo), '("domains", IPConfigDomainsPropertyInfo), '("family", IPConfigFamilyPropertyInfo), '("gateway", IPConfigGatewayPropertyInfo), '("nameservers", IPConfigNameserversPropertyInfo), '("path", NM.Object.ObjectPathPropertyInfo), '("routes", IPConfigRoutesPropertyInfo), '("searches", IPConfigSearchesPropertyInfo), '("winsServers", IPConfigWinsServersPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
iPConfigAddresses :: AttrLabelProxy "addresses"
iPConfigAddresses = AttrLabelProxy

iPConfigDomains :: AttrLabelProxy "domains"
iPConfigDomains = AttrLabelProxy

iPConfigFamily :: AttrLabelProxy "family"
iPConfigFamily = AttrLabelProxy

iPConfigGateway :: AttrLabelProxy "gateway"
iPConfigGateway = AttrLabelProxy

iPConfigNameservers :: AttrLabelProxy "nameservers"
iPConfigNameservers = AttrLabelProxy

iPConfigRoutes :: AttrLabelProxy "routes"
iPConfigRoutes = AttrLabelProxy

iPConfigSearches :: AttrLabelProxy "searches"
iPConfigSearches = AttrLabelProxy

iPConfigWinsServers :: AttrLabelProxy "winsServers"
iPConfigWinsServers = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "nm_ip_config_get_addresses" nm_ip_config_get_addresses :: 
    Ptr IPConfig ->                         -- config : TInterface (Name {namespace = "NM", name = "IPConfig"})
    IO (Ptr (GPtrArray (Ptr NM.IPAddress.IPAddress)))

-- | Gets the IP addresses (containing the address, prefix, and gateway).
iPConfigGetAddresses ::
    (B.CallStack.HasCallStack, MonadIO m, IsIPConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.IPConfig.IPConfig'
    -> m [NM.IPAddress.IPAddress]
    -- ^ __Returns:__ the t'GI.GLib.Structs.PtrArray.PtrArray'
    -- containing t'GI.NM.Structs.IPAddress.IPAddress'es.  This is the internal copy used by the
    -- configuration and must not be modified. The library never modifies the
    -- returned array and thus it is safe for callers to reference and keep using it.
iPConfigGetAddresses :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIPConfig a) =>
a -> m [IPAddress]
iPConfigGetAddresses a
config = IO [IPAddress] -> m [IPAddress]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [IPAddress] -> m [IPAddress])
-> IO [IPAddress] -> m [IPAddress]
forall a b. (a -> b) -> a -> b
$ do
    Ptr IPConfig
config' <- a -> IO (Ptr IPConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Ptr (GPtrArray (Ptr IPAddress))
result <- Ptr IPConfig -> IO (Ptr (GPtrArray (Ptr IPAddress)))
nm_ip_config_get_addresses Ptr IPConfig
config'
    Text -> Ptr (GPtrArray (Ptr IPAddress)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iPConfigGetAddresses" Ptr (GPtrArray (Ptr IPAddress))
result
    [Ptr IPAddress]
result' <- Ptr (GPtrArray (Ptr IPAddress)) -> IO [Ptr IPAddress]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr IPAddress))
result
    [IPAddress]
result'' <- (Ptr IPAddress -> IO IPAddress)
-> [Ptr IPAddress] -> IO [IPAddress]
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 IPAddress -> IPAddress)
-> Ptr IPAddress -> IO IPAddress
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr IPAddress -> IPAddress
NM.IPAddress.IPAddress) [Ptr IPAddress]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    [IPAddress] -> IO [IPAddress]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [IPAddress]
result''

#if defined(ENABLE_OVERLOADING)
data IPConfigGetAddressesMethodInfo
instance (signature ~ (m [NM.IPAddress.IPAddress]), MonadIO m, IsIPConfig a) => O.OverloadedMethod IPConfigGetAddressesMethodInfo a signature where
    overloadedMethod = iPConfigGetAddresses

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


#endif

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

foreign import ccall "nm_ip_config_get_domains" nm_ip_config_get_domains :: 
    Ptr IPConfig ->                         -- config : TInterface (Name {namespace = "NM", name = "IPConfig"})
    IO (Ptr CString)

-- | Gets the domain names.
iPConfigGetDomains ::
    (B.CallStack.HasCallStack, MonadIO m, IsIPConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.IPConfig.IPConfig'
    -> m [T.Text]
    -- ^ __Returns:__ the array of domains.
    -- (This is never 'P.Nothing', though it may be 0-length).
iPConfigGetDomains :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIPConfig a) =>
a -> m [Text]
iPConfigGetDomains a
config = 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 IPConfig
config' <- a -> IO (Ptr IPConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Ptr CString
result <- Ptr IPConfig -> IO (Ptr CString)
nm_ip_config_get_domains Ptr IPConfig
config'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iPConfigGetDomains" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data IPConfigGetDomainsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsIPConfig a) => O.OverloadedMethod IPConfigGetDomainsMethodInfo a signature where
    overloadedMethod = iPConfigGetDomains

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


#endif

-- method IPConfig::get_family
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "config"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "IPConfig" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMIPConfig" , 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_ip_config_get_family" nm_ip_config_get_family :: 
    Ptr IPConfig ->                         -- config : TInterface (Name {namespace = "NM", name = "IPConfig"})
    IO Int32

-- | Gets the IP address family
iPConfigGetFamily ::
    (B.CallStack.HasCallStack, MonadIO m, IsIPConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.IPConfig.IPConfig'
    -> m Int32
    -- ^ __Returns:__ the IP address family; either \<literal>AF_INET\<\/literal> or
    -- \<literal>AF_INET6\<\/literal>
iPConfigGetFamily :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIPConfig a) =>
a -> m Int32
iPConfigGetFamily a
config = 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 IPConfig
config' <- a -> IO (Ptr IPConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Int32
result <- Ptr IPConfig -> IO Int32
nm_ip_config_get_family Ptr IPConfig
config'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data IPConfigGetFamilyMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsIPConfig a) => O.OverloadedMethod IPConfigGetFamilyMethodInfo a signature where
    overloadedMethod = iPConfigGetFamily

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


#endif

-- method IPConfig::get_gateway
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "config"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "IPConfig" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMIPConfig" , 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_ip_config_get_gateway" nm_ip_config_get_gateway :: 
    Ptr IPConfig ->                         -- config : TInterface (Name {namespace = "NM", name = "IPConfig"})
    IO CString

-- | Gets the IP gateway address.
iPConfigGetGateway ::
    (B.CallStack.HasCallStack, MonadIO m, IsIPConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.IPConfig.IPConfig'
    -> m T.Text
    -- ^ __Returns:__ the IP address of the gateway.
iPConfigGetGateway :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIPConfig a) =>
a -> m Text
iPConfigGetGateway a
config = 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 IPConfig
config' <- a -> IO (Ptr IPConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    CString
result <- Ptr IPConfig -> IO CString
nm_ip_config_get_gateway Ptr IPConfig
config'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iPConfigGetGateway" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data IPConfigGetGatewayMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsIPConfig a) => O.OverloadedMethod IPConfigGetGatewayMethodInfo a signature where
    overloadedMethod = iPConfigGetGateway

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


#endif

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

foreign import ccall "nm_ip_config_get_nameservers" nm_ip_config_get_nameservers :: 
    Ptr IPConfig ->                         -- config : TInterface (Name {namespace = "NM", name = "IPConfig"})
    IO (Ptr CString)

-- | Gets the domain name servers (DNS).
iPConfigGetNameservers ::
    (B.CallStack.HasCallStack, MonadIO m, IsIPConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.IPConfig.IPConfig'
    -> m [T.Text]
    -- ^ __Returns:__ the array of nameserver IP addresses
iPConfigGetNameservers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIPConfig a) =>
a -> m [Text]
iPConfigGetNameservers a
config = 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 IPConfig
config' <- a -> IO (Ptr IPConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Ptr CString
result <- Ptr IPConfig -> IO (Ptr CString)
nm_ip_config_get_nameservers Ptr IPConfig
config'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iPConfigGetNameservers" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data IPConfigGetNameserversMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsIPConfig a) => O.OverloadedMethod IPConfigGetNameserversMethodInfo a signature where
    overloadedMethod = iPConfigGetNameservers

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


#endif

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

foreign import ccall "nm_ip_config_get_routes" nm_ip_config_get_routes :: 
    Ptr IPConfig ->                         -- config : TInterface (Name {namespace = "NM", name = "IPConfig"})
    IO (Ptr (GPtrArray (Ptr NM.IPRoute.IPRoute)))

-- | Gets the routes.
iPConfigGetRoutes ::
    (B.CallStack.HasCallStack, MonadIO m, IsIPConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.IPConfig.IPConfig'
    -> m [NM.IPRoute.IPRoute]
    -- ^ __Returns:__ the t'GI.GLib.Structs.PtrArray.PtrArray' containing
    -- t'GI.NM.Structs.IPRoute.IPRoute's. This is the internal copy used by the configuration, and must
    -- not be modified. The library never modifies the returned array and thus it is
    -- safe for callers to reference and keep using it.
iPConfigGetRoutes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIPConfig a) =>
a -> m [IPRoute]
iPConfigGetRoutes a
config = IO [IPRoute] -> m [IPRoute]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [IPRoute] -> m [IPRoute]) -> IO [IPRoute] -> m [IPRoute]
forall a b. (a -> b) -> a -> b
$ do
    Ptr IPConfig
config' <- a -> IO (Ptr IPConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Ptr (GPtrArray (Ptr IPRoute))
result <- Ptr IPConfig -> IO (Ptr (GPtrArray (Ptr IPRoute)))
nm_ip_config_get_routes Ptr IPConfig
config'
    Text -> Ptr (GPtrArray (Ptr IPRoute)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iPConfigGetRoutes" Ptr (GPtrArray (Ptr IPRoute))
result
    [Ptr IPRoute]
result' <- Ptr (GPtrArray (Ptr IPRoute)) -> IO [Ptr IPRoute]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr IPRoute))
result
    [IPRoute]
result'' <- (Ptr IPRoute -> IO IPRoute) -> [Ptr IPRoute] -> IO [IPRoute]
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 IPRoute -> IPRoute) -> Ptr IPRoute -> IO IPRoute
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr IPRoute -> IPRoute
NM.IPRoute.IPRoute) [Ptr IPRoute]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    [IPRoute] -> IO [IPRoute]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [IPRoute]
result''

#if defined(ENABLE_OVERLOADING)
data IPConfigGetRoutesMethodInfo
instance (signature ~ (m [NM.IPRoute.IPRoute]), MonadIO m, IsIPConfig a) => O.OverloadedMethod IPConfigGetRoutesMethodInfo a signature where
    overloadedMethod = iPConfigGetRoutes

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


#endif

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

foreign import ccall "nm_ip_config_get_searches" nm_ip_config_get_searches :: 
    Ptr IPConfig ->                         -- config : TInterface (Name {namespace = "NM", name = "IPConfig"})
    IO (Ptr CString)

-- | Gets the DNS searches.
iPConfigGetSearches ::
    (B.CallStack.HasCallStack, MonadIO m, IsIPConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.IPConfig.IPConfig'
    -> m [T.Text]
    -- ^ __Returns:__ the array of DNS search strings.
    -- (This is never 'P.Nothing', though it may be 0-length).
iPConfigGetSearches :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIPConfig a) =>
a -> m [Text]
iPConfigGetSearches a
config = 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 IPConfig
config' <- a -> IO (Ptr IPConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Ptr CString
result <- Ptr IPConfig -> IO (Ptr CString)
nm_ip_config_get_searches Ptr IPConfig
config'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iPConfigGetSearches" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data IPConfigGetSearchesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsIPConfig a) => O.OverloadedMethod IPConfigGetSearchesMethodInfo a signature where
    overloadedMethod = iPConfigGetSearches

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


#endif

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

foreign import ccall "nm_ip_config_get_wins_servers" nm_ip_config_get_wins_servers :: 
    Ptr IPConfig ->                         -- config : TInterface (Name {namespace = "NM", name = "IPConfig"})
    IO (Ptr CString)

-- | Gets the Windows Internet Name Service servers (WINS).
iPConfigGetWinsServers ::
    (B.CallStack.HasCallStack, MonadIO m, IsIPConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.IPConfig.IPConfig'
    -> m [T.Text]
    -- ^ __Returns:__ the arry of WINS server IP address strings.
    -- (This is never 'P.Nothing', though it may be 0-length.)
iPConfigGetWinsServers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIPConfig a) =>
a -> m [Text]
iPConfigGetWinsServers a
config = 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 IPConfig
config' <- a -> IO (Ptr IPConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Ptr CString
result <- Ptr IPConfig -> IO (Ptr CString)
nm_ip_config_get_wins_servers Ptr IPConfig
config'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iPConfigGetWinsServers" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data IPConfigGetWinsServersMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsIPConfig a) => O.OverloadedMethod IPConfigGetWinsServersMethodInfo a signature where
    overloadedMethod = iPConfigGetWinsServers

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


#endif