{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.ProxyAddressEnumerator
(
ProxyAddressEnumerator(..) ,
IsProxyAddressEnumerator ,
toProxyAddressEnumerator ,
noProxyAddressEnumerator ,
#if defined(ENABLE_OVERLOADING)
ResolveProxyAddressEnumeratorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressEnumeratorConnectablePropertyInfo,
#endif
constructProxyAddressEnumeratorConnectable,
getProxyAddressEnumeratorConnectable ,
#if defined(ENABLE_OVERLOADING)
proxyAddressEnumeratorConnectable ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressEnumeratorDefaultPortPropertyInfo,
#endif
constructProxyAddressEnumeratorDefaultPort,
getProxyAddressEnumeratorDefaultPort ,
#if defined(ENABLE_OVERLOADING)
proxyAddressEnumeratorDefaultPort ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressEnumeratorProxyResolverPropertyInfo,
#endif
clearProxyAddressEnumeratorProxyResolver,
constructProxyAddressEnumeratorProxyResolver,
getProxyAddressEnumeratorProxyResolver ,
#if defined(ENABLE_OVERLOADING)
proxyAddressEnumeratorProxyResolver ,
#endif
setProxyAddressEnumeratorProxyResolver ,
#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.ManagedPtr as B.ManagedPtr
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 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 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
newtype ProxyAddressEnumerator = ProxyAddressEnumerator (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)
foreign import ccall "g_proxy_address_enumerator_get_type"
c_g_proxy_address_enumerator_get_type :: IO GType
instance GObject ProxyAddressEnumerator where
gobjectType :: IO GType
gobjectType = IO GType
c_g_proxy_address_enumerator_get_type
instance B.GValue.IsGValue ProxyAddressEnumerator where
toGValue :: ProxyAddressEnumerator -> IO GValue
toGValue o :: ProxyAddressEnumerator
o = do
GType
gtype <- IO GType
c_g_proxy_address_enumerator_get_type
ProxyAddressEnumerator
-> (Ptr ProxyAddressEnumerator -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ProxyAddressEnumerator
o (GType
-> (GValue -> Ptr ProxyAddressEnumerator -> IO ())
-> Ptr ProxyAddressEnumerator
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ProxyAddressEnumerator -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO ProxyAddressEnumerator
fromGValue gv :: GValue
gv = do
Ptr ProxyAddressEnumerator
ptr <- GValue -> IO (Ptr ProxyAddressEnumerator)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ProxyAddressEnumerator)
(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
class (GObject o, O.IsDescendantOf ProxyAddressEnumerator o) => IsProxyAddressEnumerator o
instance (GObject o, O.IsDescendantOf ProxyAddressEnumerator o) => IsProxyAddressEnumerator o
instance O.HasParentTypes ProxyAddressEnumerator
type instance O.ParentTypes ProxyAddressEnumerator = '[Gio.SocketAddressEnumerator.SocketAddressEnumerator, GObject.Object.Object]
toProxyAddressEnumerator :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m ProxyAddressEnumerator
toProxyAddressEnumerator :: o -> m ProxyAddressEnumerator
toProxyAddressEnumerator = IO ProxyAddressEnumerator -> m ProxyAddressEnumerator
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ProxyAddressEnumerator -> ProxyAddressEnumerator
ProxyAddressEnumerator
noProxyAddressEnumerator :: Maybe ProxyAddressEnumerator
noProxyAddressEnumerator :: Maybe ProxyAddressEnumerator
noProxyAddressEnumerator = Maybe ProxyAddressEnumerator
forall a. Maybe a
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.MethodInfo 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
#endif
getProxyAddressEnumeratorConnectable :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m (Maybe Gio.SocketConnectable.SocketConnectable)
getProxyAddressEnumeratorConnectable :: o -> m (Maybe SocketConnectable)
getProxyAddressEnumeratorConnectable obj :: o
obj = IO (Maybe SocketConnectable) -> m (Maybe SocketConnectable)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "connectable" ManagedPtr SocketConnectable -> SocketConnectable
Gio.SocketConnectable.SocketConnectable
constructProxyAddressEnumeratorConnectable :: (IsProxyAddressEnumerator o, Gio.SocketConnectable.IsSocketConnectable a) => a -> IO (GValueConstruct o)
constructProxyAddressEnumeratorConnectable :: a -> IO (GValueConstruct o)
constructProxyAddressEnumeratorConnectable val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "connectable" (a -> Maybe a
forall a. a -> Maybe a
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
#endif
getProxyAddressEnumeratorDefaultPort :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m Word32
getProxyAddressEnumeratorDefaultPort :: o -> m Word32
getProxyAddressEnumeratorDefaultPort obj :: o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj "default-port"
constructProxyAddressEnumeratorDefaultPort :: (IsProxyAddressEnumerator o) => Word32 -> IO (GValueConstruct o)
constructProxyAddressEnumeratorDefaultPort :: Word32 -> IO (GValueConstruct o)
constructProxyAddressEnumeratorDefaultPort val :: Word32
val = String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 "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
#endif
getProxyAddressEnumeratorProxyResolver :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m (Maybe Gio.ProxyResolver.ProxyResolver)
getProxyAddressEnumeratorProxyResolver :: o -> m (Maybe ProxyResolver)
getProxyAddressEnumeratorProxyResolver obj :: o
obj = IO (Maybe ProxyResolver) -> m (Maybe ProxyResolver)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "proxy-resolver" ManagedPtr ProxyResolver -> ProxyResolver
Gio.ProxyResolver.ProxyResolver
setProxyAddressEnumeratorProxyResolver :: (MonadIO m, IsProxyAddressEnumerator o, Gio.ProxyResolver.IsProxyResolver a) => o -> a -> m ()
setProxyAddressEnumeratorProxyResolver :: o -> a -> m ()
setProxyAddressEnumeratorProxyResolver obj :: o
obj val :: a
val = 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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "proxy-resolver" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructProxyAddressEnumeratorProxyResolver :: (IsProxyAddressEnumerator o, Gio.ProxyResolver.IsProxyResolver a) => a -> IO (GValueConstruct o)
constructProxyAddressEnumeratorProxyResolver :: a -> IO (GValueConstruct o)
constructProxyAddressEnumeratorProxyResolver val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "proxy-resolver" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
clearProxyAddressEnumeratorProxyResolver :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m ()
clearProxyAddressEnumeratorProxyResolver :: o -> m ()
clearProxyAddressEnumeratorProxyResolver obj :: 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 "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
#endif
getProxyAddressEnumeratorUri :: (MonadIO m, IsProxyAddressEnumerator o) => o -> m (Maybe T.Text)
getProxyAddressEnumeratorUri :: o -> m (Maybe Text)
getProxyAddressEnumeratorUri obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "uri"
constructProxyAddressEnumeratorUri :: (IsProxyAddressEnumerator o) => T.Text -> IO (GValueConstruct o)
constructProxyAddressEnumeratorUri :: Text -> IO (GValueConstruct o)
constructProxyAddressEnumeratorUri val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "uri" (Text -> Maybe Text
forall a. a -> Maybe a
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
#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