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

-- * Exported types
    DhcpConfig(..)                          ,
    IsDhcpConfig                            ,
    toDhcpConfig                            ,


 -- * 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
-- [getClient]("GI.NM.Objects.Object#g:method:getClient"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFamily]("GI.NM.Objects.DhcpConfig#g:method:getFamily"), [getOneOption]("GI.NM.Objects.DhcpConfig#g:method:getOneOption"), [getOptions]("GI.NM.Objects.DhcpConfig#g:method:getOptions"), [getPath]("GI.NM.Objects.Object#g:method:getPath"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== 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)
    ResolveDhcpConfigMethod                 ,
#endif

-- ** getFamily #method:getFamily#

#if defined(ENABLE_OVERLOADING)
    DhcpConfigGetFamilyMethodInfo           ,
#endif
    dhcpConfigGetFamily                     ,


-- ** getOneOption #method:getOneOption#

#if defined(ENABLE_OVERLOADING)
    DhcpConfigGetOneOptionMethodInfo        ,
#endif
    dhcpConfigGetOneOption                  ,


-- ** getOptions #method:getOptions#

#if defined(ENABLE_OVERLOADING)
    DhcpConfigGetOptionsMethodInfo          ,
#endif
    dhcpConfigGetOptions                    ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DhcpConfigFamilyPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    dhcpConfigFamily                        ,
#endif
    getDhcpConfigFamily                     ,


-- ** options #attr:options#
-- | The t'GI.GLib.Structs.HashTable.HashTable' containing options of the configuration.

#if defined(ENABLE_OVERLOADING)
    DhcpConfigOptionsPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dhcpConfigOptions                       ,
#endif
    getDhcpConfigOptions                    ,




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

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

#endif

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

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

foreign import ccall "nm_dhcp_config_get_type"
    c_nm_dhcp_config_get_type :: IO B.Types.GType

instance B.Types.TypedObject DhcpConfig where
    glibType :: IO GType
glibType = IO GType
c_nm_dhcp_config_get_type

instance B.Types.GObject DhcpConfig

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

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

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

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

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

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

#endif

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

#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' dhcpConfig #family
-- @
getDhcpConfigFamily :: (MonadIO m, IsDhcpConfig o) => o -> m Int32
getDhcpConfigFamily :: forall (m :: * -> *) o. (MonadIO m, IsDhcpConfig o) => o -> m Int32
getDhcpConfigFamily 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 DhcpConfigFamilyPropertyInfo
instance AttrInfo DhcpConfigFamilyPropertyInfo where
    type AttrAllowedOps DhcpConfigFamilyPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DhcpConfigFamilyPropertyInfo = IsDhcpConfig
    type AttrSetTypeConstraint DhcpConfigFamilyPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DhcpConfigFamilyPropertyInfo = (~) ()
    type AttrTransferType DhcpConfigFamilyPropertyInfo = ()
    type AttrGetType DhcpConfigFamilyPropertyInfo = Int32
    type AttrLabel DhcpConfigFamilyPropertyInfo = "family"
    type AttrOrigin DhcpConfigFamilyPropertyInfo = DhcpConfig
    attrGet = getDhcpConfigFamily
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.DhcpConfig.family"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-DhcpConfig.html#g:attr:family"
        })
#endif

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

-- | Get the value of the “@options@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dhcpConfig #options
-- @
getDhcpConfigOptions :: (MonadIO m, IsDhcpConfig o) => o -> m (Map.Map T.Text T.Text)
getDhcpConfigOptions :: forall (m :: * -> *) o.
(MonadIO m, IsDhcpConfig o) =>
o -> m (Map Text Text)
getDhcpConfigOptions o
obj = IO (Map Text Text) -> m (Map Text Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Map Text Text) -> m (Map Text Text))
-> IO (Map Text Text) -> m (Map Text Text)
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe (Map Text Text)) -> IO (Map Text Text)
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDhcpConfigOptions" (IO (Maybe (Map Text Text)) -> IO (Map Text Text))
-> IO (Maybe (Map Text Text)) -> IO (Map Text Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe (Map Text Text))
forall a b. GObject a => a -> String -> IO b
B.Properties.getObjectPropertyHash o
obj String
"options"

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DhcpConfig
type instance O.AttributeList DhcpConfig = DhcpConfigAttributeList
type DhcpConfigAttributeList = ('[ '("client", NM.Object.ObjectClientPropertyInfo), '("family", DhcpConfigFamilyPropertyInfo), '("options", DhcpConfigOptionsPropertyInfo), '("path", NM.Object.ObjectPathPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
dhcpConfigFamily :: AttrLabelProxy "family"
dhcpConfigFamily = AttrLabelProxy

dhcpConfigOptions :: AttrLabelProxy "options"
dhcpConfigOptions = AttrLabelProxy

#endif

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

#endif

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

-- | Gets the IP address family of the configuration
dhcpConfigGetFamily ::
    (B.CallStack.HasCallStack, MonadIO m, IsDhcpConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.DhcpConfig.DhcpConfig'
    -> m Int32
    -- ^ __Returns:__ the IP address family; either \<literal>AF_INET\<\/literal> or
    --   \<literal>AF_INET6\<\/literal>
dhcpConfigGetFamily :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDhcpConfig a) =>
a -> m Int32
dhcpConfigGetFamily 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 DhcpConfig
config' <- a -> IO (Ptr DhcpConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Int32
result <- Ptr DhcpConfig -> IO Int32
nm_dhcp_config_get_family Ptr DhcpConfig
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 DhcpConfigGetFamilyMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDhcpConfig a) => O.OverloadedMethod DhcpConfigGetFamilyMethodInfo a signature where
    overloadedMethod = dhcpConfigGetFamily

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


#endif

-- method DhcpConfig::get_one_option
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "config"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "DhcpConfig" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #NMDhcpConfig" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the option to retrieve"
--                 , 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_dhcp_config_get_one_option" nm_dhcp_config_get_one_option :: 
    Ptr DhcpConfig ->                       -- config : TInterface (Name {namespace = "NM", name = "DhcpConfig"})
    CString ->                              -- option : TBasicType TUTF8
    IO CString

-- | Gets one option by option name.
dhcpConfigGetOneOption ::
    (B.CallStack.HasCallStack, MonadIO m, IsDhcpConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.DhcpConfig.DhcpConfig'
    -> T.Text
    -- ^ /@option@/: the option to retrieve
    -> m T.Text
    -- ^ __Returns:__ the configuration option\'s value. This is the internal string used by the
    -- configuration, and must not be modified.
dhcpConfigGetOneOption :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDhcpConfig a) =>
a -> Text -> m Text
dhcpConfigGetOneOption a
config Text
option = 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 DhcpConfig
config' <- a -> IO (Ptr DhcpConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    CString
option' <- Text -> IO CString
textToCString Text
option
    CString
result <- Ptr DhcpConfig -> CString -> IO CString
nm_dhcp_config_get_one_option Ptr DhcpConfig
config' CString
option'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dhcpConfigGetOneOption" 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
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
option'
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DhcpConfigGetOneOptionMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDhcpConfig a) => O.OverloadedMethod DhcpConfigGetOneOptionMethodInfo a signature where
    overloadedMethod = dhcpConfigGetOneOption

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


#endif

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

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

-- | Gets all the options contained in the configuration.
dhcpConfigGetOptions ::
    (B.CallStack.HasCallStack, MonadIO m, IsDhcpConfig a) =>
    a
    -- ^ /@config@/: a t'GI.NM.Objects.DhcpConfig.DhcpConfig'
    -> m (Map.Map T.Text T.Text)
    -- ^ __Returns:__ the t'GI.GLib.Structs.HashTable.HashTable' containing
    -- strings for keys and values.  This is the internal copy used by the
    -- configuration, and must not be modified.
dhcpConfigGetOptions :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDhcpConfig a) =>
a -> m (Map Text Text)
dhcpConfigGetOptions a
config = IO (Map Text Text) -> m (Map Text Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Map Text Text) -> m (Map Text Text))
-> IO (Map Text Text) -> m (Map Text Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DhcpConfig
config' <- a -> IO (Ptr DhcpConfig)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
config
    Ptr (GHashTable CString CString)
result <- Ptr DhcpConfig -> IO (Ptr (GHashTable CString CString))
nm_dhcp_config_get_options Ptr DhcpConfig
config'
    Text -> Ptr (GHashTable CString CString) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dhcpConfigGetOptions" Ptr (GHashTable CString CString)
result
    [(PtrWrapped CString, PtrWrapped CString)]
result' <- Ptr (GHashTable CString CString)
-> IO [(PtrWrapped CString, PtrWrapped CString)]
forall a b.
Ptr (GHashTable a b) -> IO [(PtrWrapped a, PtrWrapped b)]
unpackGHashTable Ptr (GHashTable CString CString)
result
    let result'' :: [(CString, PtrWrapped CString)]
result'' = (PtrWrapped CString -> CString)
-> [(PtrWrapped CString, PtrWrapped CString)]
-> [(CString, PtrWrapped CString)]
forall a c b. (a -> c) -> [(a, b)] -> [(c, b)]
mapFirst PtrWrapped CString -> CString
B.GHT.cstringUnpackPtr [(PtrWrapped CString, PtrWrapped CString)]
result'
    [(Text, PtrWrapped CString)]
result''' <- (CString -> IO Text)
-> [(CString, PtrWrapped CString)]
-> IO [(Text, PtrWrapped CString)]
forall (f :: * -> *) a c b.
Applicative f =>
(a -> f c) -> [(a, b)] -> f [(c, b)]
mapFirstA HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [(CString, PtrWrapped CString)]
result''
    let result'''' :: [(Text, CString)]
result'''' = (PtrWrapped CString -> CString)
-> [(Text, PtrWrapped CString)] -> [(Text, CString)]
forall b c a. (b -> c) -> [(a, b)] -> [(a, c)]
mapSecond PtrWrapped CString -> CString
B.GHT.cstringUnpackPtr [(Text, PtrWrapped CString)]
result'''
    [(Text, Text)]
result''''' <- (CString -> IO Text) -> [(Text, CString)] -> IO [(Text, Text)]
forall (f :: * -> *) b c a.
Applicative f =>
(b -> f c) -> [(a, b)] -> f [(a, c)]
mapSecondA HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [(Text, CString)]
result''''
    let result'''''' :: Map Text Text
result'''''' = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
result'''''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
config
    Map Text Text -> IO (Map Text Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Map Text Text
result''''''

#if defined(ENABLE_OVERLOADING)
data DhcpConfigGetOptionsMethodInfo
instance (signature ~ (m (Map.Map T.Text T.Text)), MonadIO m, IsDhcpConfig a) => O.OverloadedMethod DhcpConfigGetOptionsMethodInfo a signature where
    overloadedMethod = dhcpConfigGetOptions

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


#endif