{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.ProxyAddressEnumerator.ProxyAddressEnumerator' is a wrapper around t'GI.Gio.Objects.SocketAddressEnumerator.SocketAddressEnumerator' which
-- takes the t'GI.Gio.Objects.SocketAddress.SocketAddress' instances returned by the t'GI.Gio.Objects.SocketAddressEnumerator.SocketAddressEnumerator'
-- and wraps them in t'GI.Gio.Objects.ProxyAddress.ProxyAddress' instances, using the given
-- [ProxyAddressEnumerator:proxyResolver]("GI.Gio.Objects.ProxyAddressEnumerator#g:attr:proxyResolver").
-- 
-- This enumerator will be returned (for example, by
-- 'GI.Gio.Interfaces.SocketConnectable.socketConnectableEnumerate') as appropriate when a proxy is configured;
-- there should be no need to manually wrap a t'GI.Gio.Objects.SocketAddressEnumerator.SocketAddressEnumerator' instance
-- with one.

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

module GI.Gio.Objects.ProxyAddressEnumerator
    ( 

-- * Exported types
    ProxyAddressEnumerator(..)              ,
    IsProxyAddressEnumerator                ,
    toProxyAddressEnumerator                ,


 -- * 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"), [next]("GI.Gio.Objects.SocketAddressEnumerator#g:method:next"), [nextAsync]("GI.Gio.Objects.SocketAddressEnumerator#g:method:nextAsync"), [nextFinish]("GI.Gio.Objects.SocketAddressEnumerator#g:method:nextFinish"), [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
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [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)
    ResolveProxyAddressEnumeratorMethod     ,
#endif



 -- * Properties


-- ** connectable #attr:connectable#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ProxyAddressEnumeratorConnectablePropertyInfo,
#endif
    constructProxyAddressEnumeratorConnectable,
    getProxyAddressEnumeratorConnectable    ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressEnumeratorConnectable       ,
#endif


-- ** defaultPort #attr:defaultPort#
-- | The default port to use if [ProxyAddressEnumerator:uri]("GI.Gio.Objects.ProxyAddressEnumerator#g:attr:uri") does not
-- specify one.
-- 
-- /Since: 2.38/

#if defined(ENABLE_OVERLOADING)
    ProxyAddressEnumeratorDefaultPortPropertyInfo,
#endif
    constructProxyAddressEnumeratorDefaultPort,
    getProxyAddressEnumeratorDefaultPort    ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressEnumeratorDefaultPort       ,
#endif


-- ** proxyResolver #attr:proxyResolver#
-- | The proxy resolver to use.
-- 
-- /Since: 2.36/

#if defined(ENABLE_OVERLOADING)
    ProxyAddressEnumeratorProxyResolverPropertyInfo,
#endif
    clearProxyAddressEnumeratorProxyResolver,
    constructProxyAddressEnumeratorProxyResolver,
    getProxyAddressEnumeratorProxyResolver  ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressEnumeratorProxyResolver     ,
#endif
    setProxyAddressEnumeratorProxyResolver  ,


-- ** uri #attr:uri#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ProxyAddressEnumeratorUriPropertyInfo   ,
#endif
    constructProxyAddressEnumeratorUri      ,
    getProxyAddressEnumeratorUri            ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressEnumeratorUri               ,
#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.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.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 GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.ProxyResolver as Gio.ProxyResolver
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddressEnumerator as Gio.SocketAddressEnumerator

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

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

foreign import ccall "g_proxy_address_enumerator_get_type"
    c_g_proxy_address_enumerator_get_type :: IO B.Types.GType

instance B.Types.TypedObject ProxyAddressEnumerator where
    glibType :: IO GType
glibType = IO GType
c_g_proxy_address_enumerator_get_type

instance B.Types.GObject ProxyAddressEnumerator

-- | Type class for types which can be safely cast to `ProxyAddressEnumerator`, for instance with `toProxyAddressEnumerator`.
class (SP.GObject o, O.IsDescendantOf ProxyAddressEnumerator o) => IsProxyAddressEnumerator o
instance (SP.GObject o, O.IsDescendantOf ProxyAddressEnumerator o) => IsProxyAddressEnumerator o

instance O.HasParentTypes ProxyAddressEnumerator
type instance O.ParentTypes ProxyAddressEnumerator = '[Gio.SocketAddressEnumerator.SocketAddressEnumerator, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveProxyAddressEnumeratorMethod (t :: Symbol) (o :: *) :: * where
    ResolveProxyAddressEnumeratorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveProxyAddressEnumeratorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveProxyAddressEnumeratorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveProxyAddressEnumeratorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveProxyAddressEnumeratorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveProxyAddressEnumeratorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveProxyAddressEnumeratorMethod "next" o = Gio.SocketAddressEnumerator.SocketAddressEnumeratorNextMethodInfo
    ResolveProxyAddressEnumeratorMethod "nextAsync" o = Gio.SocketAddressEnumerator.SocketAddressEnumeratorNextAsyncMethodInfo
    ResolveProxyAddressEnumeratorMethod "nextFinish" o = Gio.SocketAddressEnumerator.SocketAddressEnumeratorNextFinishMethodInfo
    ResolveProxyAddressEnumeratorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveProxyAddressEnumeratorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveProxyAddressEnumeratorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveProxyAddressEnumeratorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveProxyAddressEnumeratorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveProxyAddressEnumeratorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveProxyAddressEnumeratorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveProxyAddressEnumeratorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveProxyAddressEnumeratorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveProxyAddressEnumeratorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveProxyAddressEnumeratorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveProxyAddressEnumeratorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveProxyAddressEnumeratorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveProxyAddressEnumeratorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveProxyAddressEnumeratorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveProxyAddressEnumeratorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveProxyAddressEnumeratorMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "connectable"
   -- Type: TInterface (Name {namespace = "Gio", name = "SocketConnectable"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@connectable@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' proxyAddressEnumerator #connectable
-- @
getProxyAddressEnumeratorConnectable :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m (Maybe Gio.SocketConnectable.SocketConnectable)
getProxyAddressEnumeratorConnectable :: forall (m :: * -> *) o.
(MonadIO m, IsProxyAddressEnumerator o) =>
o -> m (Maybe SocketConnectable)
getProxyAddressEnumeratorConnectable o
obj = IO (Maybe SocketConnectable) -> m (Maybe SocketConnectable)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe SocketConnectable) -> m (Maybe SocketConnectable))
-> IO (Maybe SocketConnectable) -> m (Maybe SocketConnectable)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr SocketConnectable -> SocketConnectable)
-> IO (Maybe SocketConnectable)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"connectable" ManagedPtr SocketConnectable -> SocketConnectable
Gio.SocketConnectable.SocketConnectable

-- | Construct a `GValueConstruct` with valid value for the “@connectable@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressEnumeratorConnectable :: (IsProxyAddressEnumerator o, MIO.MonadIO m, Gio.SocketConnectable.IsSocketConnectable a) => a -> m (GValueConstruct o)
constructProxyAddressEnumeratorConnectable :: forall o (m :: * -> *) a.
(IsProxyAddressEnumerator o, MonadIO m, IsSocketConnectable a) =>
a -> m (GValueConstruct o)
constructProxyAddressEnumeratorConnectable a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"connectable" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ProxyAddressEnumeratorConnectablePropertyInfo
instance AttrInfo ProxyAddressEnumeratorConnectablePropertyInfo where
    type AttrAllowedOps ProxyAddressEnumeratorConnectablePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ProxyAddressEnumeratorConnectablePropertyInfo = IsProxyAddressEnumerator
    type AttrSetTypeConstraint ProxyAddressEnumeratorConnectablePropertyInfo = Gio.SocketConnectable.IsSocketConnectable
    type AttrTransferTypeConstraint ProxyAddressEnumeratorConnectablePropertyInfo = Gio.SocketConnectable.IsSocketConnectable
    type AttrTransferType ProxyAddressEnumeratorConnectablePropertyInfo = Gio.SocketConnectable.SocketConnectable
    type AttrGetType ProxyAddressEnumeratorConnectablePropertyInfo = (Maybe Gio.SocketConnectable.SocketConnectable)
    type AttrLabel ProxyAddressEnumeratorConnectablePropertyInfo = "connectable"
    type AttrOrigin ProxyAddressEnumeratorConnectablePropertyInfo = ProxyAddressEnumerator
    attrGet = getProxyAddressEnumeratorConnectable
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.SocketConnectable.SocketConnectable v
    attrConstruct = constructProxyAddressEnumeratorConnectable
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddressEnumerator.connectable"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-ProxyAddressEnumerator.html#g:attr:connectable"
        })
#endif

-- VVV Prop "default-port"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@default-port@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' proxyAddressEnumerator #defaultPort
-- @
getProxyAddressEnumeratorDefaultPort :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m Word32
getProxyAddressEnumeratorDefaultPort :: forall (m :: * -> *) o.
(MonadIO m, IsProxyAddressEnumerator o) =>
o -> m Word32
getProxyAddressEnumeratorDefaultPort o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"default-port"

-- | Construct a `GValueConstruct` with valid value for the “@default-port@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressEnumeratorDefaultPort :: (IsProxyAddressEnumerator o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructProxyAddressEnumeratorDefaultPort :: forall o (m :: * -> *).
(IsProxyAddressEnumerator o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructProxyAddressEnumeratorDefaultPort Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"default-port" Word32
val

#if defined(ENABLE_OVERLOADING)
data ProxyAddressEnumeratorDefaultPortPropertyInfo
instance AttrInfo ProxyAddressEnumeratorDefaultPortPropertyInfo where
    type AttrAllowedOps ProxyAddressEnumeratorDefaultPortPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ProxyAddressEnumeratorDefaultPortPropertyInfo = IsProxyAddressEnumerator
    type AttrSetTypeConstraint ProxyAddressEnumeratorDefaultPortPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint ProxyAddressEnumeratorDefaultPortPropertyInfo = (~) Word32
    type AttrTransferType ProxyAddressEnumeratorDefaultPortPropertyInfo = Word32
    type AttrGetType ProxyAddressEnumeratorDefaultPortPropertyInfo = Word32
    type AttrLabel ProxyAddressEnumeratorDefaultPortPropertyInfo = "default-port"
    type AttrOrigin ProxyAddressEnumeratorDefaultPortPropertyInfo = ProxyAddressEnumerator
    attrGet = getProxyAddressEnumeratorDefaultPort
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructProxyAddressEnumeratorDefaultPort
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddressEnumerator.defaultPort"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-ProxyAddressEnumerator.html#g:attr:defaultPort"
        })
#endif

-- VVV Prop "proxy-resolver"
   -- Type: TInterface (Name {namespace = "Gio", name = "ProxyResolver"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@proxy-resolver@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' proxyAddressEnumerator #proxyResolver
-- @
getProxyAddressEnumeratorProxyResolver :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m (Maybe Gio.ProxyResolver.ProxyResolver)
getProxyAddressEnumeratorProxyResolver :: forall (m :: * -> *) o.
(MonadIO m, IsProxyAddressEnumerator o) =>
o -> m (Maybe ProxyResolver)
getProxyAddressEnumeratorProxyResolver o
obj = IO (Maybe ProxyResolver) -> m (Maybe ProxyResolver)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe ProxyResolver) -> m (Maybe ProxyResolver))
-> IO (Maybe ProxyResolver) -> m (Maybe ProxyResolver)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ProxyResolver -> ProxyResolver)
-> IO (Maybe ProxyResolver)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"proxy-resolver" ManagedPtr ProxyResolver -> ProxyResolver
Gio.ProxyResolver.ProxyResolver

-- | Set the value of the “@proxy-resolver@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' proxyAddressEnumerator [ #proxyResolver 'Data.GI.Base.Attributes.:=' value ]
-- @
setProxyAddressEnumeratorProxyResolver :: (MonadIO m, IsProxyAddressEnumerator o, Gio.ProxyResolver.IsProxyResolver a) => o -> a -> m ()
setProxyAddressEnumeratorProxyResolver :: forall (m :: * -> *) o a.
(MonadIO m, IsProxyAddressEnumerator o, IsProxyResolver a) =>
o -> a -> m ()
setProxyAddressEnumeratorProxyResolver o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"proxy-resolver" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@proxy-resolver@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressEnumeratorProxyResolver :: (IsProxyAddressEnumerator o, MIO.MonadIO m, Gio.ProxyResolver.IsProxyResolver a) => a -> m (GValueConstruct o)
constructProxyAddressEnumeratorProxyResolver :: forall o (m :: * -> *) a.
(IsProxyAddressEnumerator o, MonadIO m, IsProxyResolver a) =>
a -> m (GValueConstruct o)
constructProxyAddressEnumeratorProxyResolver a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"proxy-resolver" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@proxy-resolver@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #proxyResolver
-- @
clearProxyAddressEnumeratorProxyResolver :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m ()
clearProxyAddressEnumeratorProxyResolver :: forall (m :: * -> *) o.
(MonadIO m, IsProxyAddressEnumerator o) =>
o -> m ()
clearProxyAddressEnumeratorProxyResolver o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe ProxyResolver -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"proxy-resolver" (Maybe ProxyResolver
forall a. Maybe a
Nothing :: Maybe Gio.ProxyResolver.ProxyResolver)

#if defined(ENABLE_OVERLOADING)
data ProxyAddressEnumeratorProxyResolverPropertyInfo
instance AttrInfo ProxyAddressEnumeratorProxyResolverPropertyInfo where
    type AttrAllowedOps ProxyAddressEnumeratorProxyResolverPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ProxyAddressEnumeratorProxyResolverPropertyInfo = IsProxyAddressEnumerator
    type AttrSetTypeConstraint ProxyAddressEnumeratorProxyResolverPropertyInfo = Gio.ProxyResolver.IsProxyResolver
    type AttrTransferTypeConstraint ProxyAddressEnumeratorProxyResolverPropertyInfo = Gio.ProxyResolver.IsProxyResolver
    type AttrTransferType ProxyAddressEnumeratorProxyResolverPropertyInfo = Gio.ProxyResolver.ProxyResolver
    type AttrGetType ProxyAddressEnumeratorProxyResolverPropertyInfo = (Maybe Gio.ProxyResolver.ProxyResolver)
    type AttrLabel ProxyAddressEnumeratorProxyResolverPropertyInfo = "proxy-resolver"
    type AttrOrigin ProxyAddressEnumeratorProxyResolverPropertyInfo = ProxyAddressEnumerator
    attrGet = getProxyAddressEnumeratorProxyResolver
    attrSet = setProxyAddressEnumeratorProxyResolver
    attrTransfer _ v = do
        unsafeCastTo Gio.ProxyResolver.ProxyResolver v
    attrConstruct = constructProxyAddressEnumeratorProxyResolver
    attrClear = clearProxyAddressEnumeratorProxyResolver
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddressEnumerator.proxyResolver"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-ProxyAddressEnumerator.html#g:attr:proxyResolver"
        })
#endif

-- VVV Prop "uri"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' proxyAddressEnumerator #uri
-- @
getProxyAddressEnumeratorUri :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m (Maybe T.Text)
getProxyAddressEnumeratorUri :: forall (m :: * -> *) o.
(MonadIO m, IsProxyAddressEnumerator o) =>
o -> m (Maybe Text)
getProxyAddressEnumeratorUri o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe 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
"uri"

-- | Construct a `GValueConstruct` with valid value for the “@uri@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressEnumeratorUri :: (IsProxyAddressEnumerator o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressEnumeratorUri :: forall o (m :: * -> *).
(IsProxyAddressEnumerator o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressEnumeratorUri Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"uri" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data ProxyAddressEnumeratorUriPropertyInfo
instance AttrInfo ProxyAddressEnumeratorUriPropertyInfo where
    type AttrAllowedOps ProxyAddressEnumeratorUriPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ProxyAddressEnumeratorUriPropertyInfo = IsProxyAddressEnumerator
    type AttrSetTypeConstraint ProxyAddressEnumeratorUriPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ProxyAddressEnumeratorUriPropertyInfo = (~) T.Text
    type AttrTransferType ProxyAddressEnumeratorUriPropertyInfo = T.Text
    type AttrGetType ProxyAddressEnumeratorUriPropertyInfo = (Maybe T.Text)
    type AttrLabel ProxyAddressEnumeratorUriPropertyInfo = "uri"
    type AttrOrigin ProxyAddressEnumeratorUriPropertyInfo = ProxyAddressEnumerator
    attrGet = getProxyAddressEnumeratorUri
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructProxyAddressEnumeratorUri
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddressEnumerator.uri"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-ProxyAddressEnumerator.html#g:attr:uri"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ProxyAddressEnumerator
type instance O.AttributeList ProxyAddressEnumerator = ProxyAddressEnumeratorAttributeList
type ProxyAddressEnumeratorAttributeList = ('[ '("connectable", ProxyAddressEnumeratorConnectablePropertyInfo), '("defaultPort", ProxyAddressEnumeratorDefaultPortPropertyInfo), '("proxyResolver", ProxyAddressEnumeratorProxyResolverPropertyInfo), '("uri", ProxyAddressEnumeratorUriPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
proxyAddressEnumeratorConnectable :: AttrLabelProxy "connectable"
proxyAddressEnumeratorConnectable = AttrLabelProxy

proxyAddressEnumeratorDefaultPort :: AttrLabelProxy "defaultPort"
proxyAddressEnumeratorDefaultPort = AttrLabelProxy

proxyAddressEnumeratorProxyResolver :: AttrLabelProxy "proxyResolver"
proxyAddressEnumeratorProxyResolver = AttrLabelProxy

proxyAddressEnumeratorUri :: AttrLabelProxy "uri"
proxyAddressEnumeratorUri = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ProxyAddressEnumerator = ProxyAddressEnumeratorSignalList
type ProxyAddressEnumeratorSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif