{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Support for proxied t'GI.Gio.Objects.InetSocketAddress.InetSocketAddress'.
-- 
-- /Since: 2.26/

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

module GI.Gio.Objects.ProxyAddress
    ( 

-- * Exported types
    ProxyAddress(..)                        ,
    IsProxyAddress                          ,
    toProxyAddress                          ,


 -- * 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"), [enumerate]("GI.Gio.Interfaces.SocketConnectable#g:method:enumerate"), [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"), [proxyEnumerate]("GI.Gio.Interfaces.SocketConnectable#g:method:proxyEnumerate"), [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"), [toNative]("GI.Gio.Objects.SocketAddress#g:method:toNative"), [toString]("GI.Gio.Interfaces.SocketConnectable#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAddress]("GI.Gio.Objects.InetSocketAddress#g:method:getAddress"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDestinationHostname]("GI.Gio.Objects.ProxyAddress#g:method:getDestinationHostname"), [getDestinationPort]("GI.Gio.Objects.ProxyAddress#g:method:getDestinationPort"), [getDestinationProtocol]("GI.Gio.Objects.ProxyAddress#g:method:getDestinationProtocol"), [getFamily]("GI.Gio.Objects.SocketAddress#g:method:getFamily"), [getFlowinfo]("GI.Gio.Objects.InetSocketAddress#g:method:getFlowinfo"), [getNativeSize]("GI.Gio.Objects.SocketAddress#g:method:getNativeSize"), [getPassword]("GI.Gio.Objects.ProxyAddress#g:method:getPassword"), [getPort]("GI.Gio.Objects.InetSocketAddress#g:method:getPort"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getProtocol]("GI.Gio.Objects.ProxyAddress#g:method:getProtocol"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getScopeId]("GI.Gio.Objects.InetSocketAddress#g:method:getScopeId"), [getUri]("GI.Gio.Objects.ProxyAddress#g:method:getUri"), [getUsername]("GI.Gio.Objects.ProxyAddress#g:method:getUsername").
-- 
-- ==== 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)
    ResolveProxyAddressMethod               ,
#endif

-- ** getDestinationHostname #method:getDestinationHostname#

#if defined(ENABLE_OVERLOADING)
    ProxyAddressGetDestinationHostnameMethodInfo,
#endif
    proxyAddressGetDestinationHostname      ,


-- ** getDestinationPort #method:getDestinationPort#

#if defined(ENABLE_OVERLOADING)
    ProxyAddressGetDestinationPortMethodInfo,
#endif
    proxyAddressGetDestinationPort          ,


-- ** getDestinationProtocol #method:getDestinationProtocol#

#if defined(ENABLE_OVERLOADING)
    ProxyAddressGetDestinationProtocolMethodInfo,
#endif
    proxyAddressGetDestinationProtocol      ,


-- ** getPassword #method:getPassword#

#if defined(ENABLE_OVERLOADING)
    ProxyAddressGetPasswordMethodInfo       ,
#endif
    proxyAddressGetPassword                 ,


-- ** getProtocol #method:getProtocol#

#if defined(ENABLE_OVERLOADING)
    ProxyAddressGetProtocolMethodInfo       ,
#endif
    proxyAddressGetProtocol                 ,


-- ** getUri #method:getUri#

#if defined(ENABLE_OVERLOADING)
    ProxyAddressGetUriMethodInfo            ,
#endif
    proxyAddressGetUri                      ,


-- ** getUsername #method:getUsername#

#if defined(ENABLE_OVERLOADING)
    ProxyAddressGetUsernameMethodInfo       ,
#endif
    proxyAddressGetUsername                 ,


-- ** new #method:new#

    proxyAddressNew                         ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    ProxyAddressDestinationHostnamePropertyInfo,
#endif
    constructProxyAddressDestinationHostname,
    getProxyAddressDestinationHostname      ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressDestinationHostname         ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    ProxyAddressDestinationPortPropertyInfo ,
#endif
    constructProxyAddressDestinationPort    ,
    getProxyAddressDestinationPort          ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressDestinationPort             ,
#endif


-- ** destinationProtocol #attr:destinationProtocol#
-- | The protocol being spoke to the destination host, or 'P.Nothing' if
-- the t'GI.Gio.Objects.ProxyAddress.ProxyAddress' doesn\'t know.
-- 
-- /Since: 2.34/

#if defined(ENABLE_OVERLOADING)
    ProxyAddressDestinationProtocolPropertyInfo,
#endif
    constructProxyAddressDestinationProtocol,
    getProxyAddressDestinationProtocol      ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressDestinationProtocol         ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    ProxyAddressPasswordPropertyInfo        ,
#endif
    constructProxyAddressPassword           ,
    getProxyAddressPassword                 ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressPassword                    ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    ProxyAddressProtocolPropertyInfo        ,
#endif
    constructProxyAddressProtocol           ,
    getProxyAddressProtocol                 ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressProtocol                    ,
#endif


-- ** uri #attr:uri#
-- | The URI string that the proxy was constructed from (or 'P.Nothing'
-- if the creator didn\'t specify this).
-- 
-- /Since: 2.34/

#if defined(ENABLE_OVERLOADING)
    ProxyAddressUriPropertyInfo             ,
#endif
    constructProxyAddressUri                ,
    getProxyAddressUri                      ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressUri                         ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    ProxyAddressUsernamePropertyInfo        ,
#endif
    constructProxyAddressUsername           ,
    getProxyAddressUsername                 ,
#if defined(ENABLE_OVERLOADING)
    proxyAddressUsername                    ,
#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.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.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.InetAddress as Gio.InetAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.InetSocketAddress as Gio.InetSocketAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress

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

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

foreign import ccall "g_proxy_address_get_type"
    c_g_proxy_address_get_type :: IO B.Types.GType

instance B.Types.TypedObject ProxyAddress where
    glibType :: IO GType
glibType = IO GType
c_g_proxy_address_get_type

instance B.Types.GObject ProxyAddress

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

instance O.HasParentTypes ProxyAddress
type instance O.ParentTypes ProxyAddress = '[Gio.InetSocketAddress.InetSocketAddress, Gio.SocketAddress.SocketAddress, GObject.Object.Object, Gio.SocketConnectable.SocketConnectable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveProxyAddressMethod (t :: Symbol) (o :: *) :: * where
    ResolveProxyAddressMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveProxyAddressMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveProxyAddressMethod "enumerate" o = Gio.SocketConnectable.SocketConnectableEnumerateMethodInfo
    ResolveProxyAddressMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveProxyAddressMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveProxyAddressMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveProxyAddressMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveProxyAddressMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveProxyAddressMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveProxyAddressMethod "proxyEnumerate" o = Gio.SocketConnectable.SocketConnectableProxyEnumerateMethodInfo
    ResolveProxyAddressMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveProxyAddressMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveProxyAddressMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveProxyAddressMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveProxyAddressMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveProxyAddressMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveProxyAddressMethod "toNative" o = Gio.SocketAddress.SocketAddressToNativeMethodInfo
    ResolveProxyAddressMethod "toString" o = Gio.SocketConnectable.SocketConnectableToStringMethodInfo
    ResolveProxyAddressMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveProxyAddressMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveProxyAddressMethod "getAddress" o = Gio.InetSocketAddress.InetSocketAddressGetAddressMethodInfo
    ResolveProxyAddressMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveProxyAddressMethod "getDestinationHostname" o = ProxyAddressGetDestinationHostnameMethodInfo
    ResolveProxyAddressMethod "getDestinationPort" o = ProxyAddressGetDestinationPortMethodInfo
    ResolveProxyAddressMethod "getDestinationProtocol" o = ProxyAddressGetDestinationProtocolMethodInfo
    ResolveProxyAddressMethod "getFamily" o = Gio.SocketAddress.SocketAddressGetFamilyMethodInfo
    ResolveProxyAddressMethod "getFlowinfo" o = Gio.InetSocketAddress.InetSocketAddressGetFlowinfoMethodInfo
    ResolveProxyAddressMethod "getNativeSize" o = Gio.SocketAddress.SocketAddressGetNativeSizeMethodInfo
    ResolveProxyAddressMethod "getPassword" o = ProxyAddressGetPasswordMethodInfo
    ResolveProxyAddressMethod "getPort" o = Gio.InetSocketAddress.InetSocketAddressGetPortMethodInfo
    ResolveProxyAddressMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveProxyAddressMethod "getProtocol" o = ProxyAddressGetProtocolMethodInfo
    ResolveProxyAddressMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveProxyAddressMethod "getScopeId" o = Gio.InetSocketAddress.InetSocketAddressGetScopeIdMethodInfo
    ResolveProxyAddressMethod "getUri" o = ProxyAddressGetUriMethodInfo
    ResolveProxyAddressMethod "getUsername" o = ProxyAddressGetUsernameMethodInfo
    ResolveProxyAddressMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveProxyAddressMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveProxyAddressMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveProxyAddressMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "destination-hostname"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@destination-hostname@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressDestinationHostname :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressDestinationHostname :: forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressDestinationHostname Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"destination-hostname" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

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

-- | Get the value of the “@destination-port@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' proxyAddress #destinationPort
-- @
getProxyAddressDestinationPort :: (MonadIO m, IsProxyAddress o) => o -> m Word32
getProxyAddressDestinationPort :: forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m Word32
getProxyAddressDestinationPort o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
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
"destination-port"

-- | Construct a `GValueConstruct` with valid value for the “@destination-port@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressDestinationPort :: (IsProxyAddress o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructProxyAddressDestinationPort :: forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructProxyAddressDestinationPort Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"destination-port" Word32
val

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

-- VVV Prop "destination-protocol"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@destination-protocol@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressDestinationProtocol :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressDestinationProtocol :: forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressDestinationProtocol Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"destination-protocol" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@password@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressPassword :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressPassword :: forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressPassword Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"password" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@protocol@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressProtocol :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressProtocol :: forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressProtocol Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"protocol" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

-- VVV Prop "uri"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,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' proxyAddress #uri
-- @
getProxyAddressUri :: (MonadIO m, IsProxyAddress o) => o -> m (Maybe T.Text)
getProxyAddressUri :: forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m (Maybe Text)
getProxyAddressUri o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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`.
constructProxyAddressUri :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressUri :: forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressUri Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 ProxyAddressUriPropertyInfo
instance AttrInfo ProxyAddressUriPropertyInfo where
    type AttrAllowedOps ProxyAddressUriPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ProxyAddressUriPropertyInfo = IsProxyAddress
    type AttrSetTypeConstraint ProxyAddressUriPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ProxyAddressUriPropertyInfo = (~) T.Text
    type AttrTransferType ProxyAddressUriPropertyInfo = T.Text
    type AttrGetType ProxyAddressUriPropertyInfo = (Maybe T.Text)
    type AttrLabel ProxyAddressUriPropertyInfo = "uri"
    type AttrOrigin ProxyAddressUriPropertyInfo = ProxyAddress
    attrGet = getProxyAddressUri
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructProxyAddressUri
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddress.uri"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ProxyAddress.html#g:attr:uri"
        })
#endif

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

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

-- | Construct a `GValueConstruct` with valid value for the “@username@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructProxyAddressUsername :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressUsername :: forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressUsername Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"username" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ProxyAddress
type instance O.AttributeList ProxyAddress = ProxyAddressAttributeList
type ProxyAddressAttributeList = ('[ '("address", Gio.InetSocketAddress.InetSocketAddressAddressPropertyInfo), '("destinationHostname", ProxyAddressDestinationHostnamePropertyInfo), '("destinationPort", ProxyAddressDestinationPortPropertyInfo), '("destinationProtocol", ProxyAddressDestinationProtocolPropertyInfo), '("family", Gio.SocketAddress.SocketAddressFamilyPropertyInfo), '("flowinfo", Gio.InetSocketAddress.InetSocketAddressFlowinfoPropertyInfo), '("password", ProxyAddressPasswordPropertyInfo), '("port", Gio.InetSocketAddress.InetSocketAddressPortPropertyInfo), '("protocol", ProxyAddressProtocolPropertyInfo), '("scopeId", Gio.InetSocketAddress.InetSocketAddressScopeIdPropertyInfo), '("uri", ProxyAddressUriPropertyInfo), '("username", ProxyAddressUsernamePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
proxyAddressDestinationHostname :: AttrLabelProxy "destinationHostname"
proxyAddressDestinationHostname = AttrLabelProxy

proxyAddressDestinationPort :: AttrLabelProxy "destinationPort"
proxyAddressDestinationPort = AttrLabelProxy

proxyAddressDestinationProtocol :: AttrLabelProxy "destinationProtocol"
proxyAddressDestinationProtocol = AttrLabelProxy

proxyAddressPassword :: AttrLabelProxy "password"
proxyAddressPassword = AttrLabelProxy

proxyAddressProtocol :: AttrLabelProxy "protocol"
proxyAddressProtocol = AttrLabelProxy

proxyAddressUri :: AttrLabelProxy "uri"
proxyAddressUri = AttrLabelProxy

proxyAddressUsername :: AttrLabelProxy "username"
proxyAddressUsername = AttrLabelProxy

#endif

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

#endif

-- method ProxyAddress::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "inetaddr"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InetAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The proxy server #GInetAddress."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "port"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The proxy server port."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "protocol"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The proxy protocol to support, in lower case (e.g. socks, http)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_hostname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The destination hostname the proxy should tunnel to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_port"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The destination port to tunnel to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "username"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The username to authenticate to the proxy server\n    (or %NULL)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "password"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The password to authenticate to the proxy server\n    (or %NULL)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "ProxyAddress" })
-- throws : False
-- Skip return : False

foreign import ccall "g_proxy_address_new" g_proxy_address_new :: 
    Ptr Gio.InetAddress.InetAddress ->      -- inetaddr : TInterface (Name {namespace = "Gio", name = "InetAddress"})
    Word16 ->                               -- port : TBasicType TUInt16
    CString ->                              -- protocol : TBasicType TUTF8
    CString ->                              -- dest_hostname : TBasicType TUTF8
    Word16 ->                               -- dest_port : TBasicType TUInt16
    CString ->                              -- username : TBasicType TUTF8
    CString ->                              -- password : TBasicType TUTF8
    IO (Ptr ProxyAddress)

-- | Creates a new t'GI.Gio.Objects.ProxyAddress.ProxyAddress' for /@inetaddr@/ with /@protocol@/ that should
-- tunnel through /@destHostname@/ and /@destPort@/.
-- 
-- (Note that this method doesn\'t set the [ProxyAddress:uri]("GI.Gio.Objects.ProxyAddress#g:attr:uri") or
-- [ProxyAddress:destinationProtocol]("GI.Gio.Objects.ProxyAddress#g:attr:destinationProtocol") fields; use @/g_object_new()/@
-- directly if you want to set those.)
-- 
-- /Since: 2.26/
proxyAddressNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.InetAddress.IsInetAddress a) =>
    a
    -- ^ /@inetaddr@/: The proxy server t'GI.Gio.Objects.InetAddress.InetAddress'.
    -> Word16
    -- ^ /@port@/: The proxy server port.
    -> T.Text
    -- ^ /@protocol@/: The proxy protocol to support, in lower case (e.g. socks, http).
    -> T.Text
    -- ^ /@destHostname@/: The destination hostname the proxy should tunnel to.
    -> Word16
    -- ^ /@destPort@/: The destination port to tunnel to.
    -> Maybe (T.Text)
    -- ^ /@username@/: The username to authenticate to the proxy server
    --     (or 'P.Nothing').
    -> Maybe (T.Text)
    -- ^ /@password@/: The password to authenticate to the proxy server
    --     (or 'P.Nothing').
    -> m ProxyAddress
    -- ^ __Returns:__ a new t'GI.Gio.Objects.ProxyAddress.ProxyAddress'
proxyAddressNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsInetAddress a) =>
a
-> Word16
-> Text
-> Text
-> Word16
-> Maybe Text
-> Maybe Text
-> m ProxyAddress
proxyAddressNew a
inetaddr Word16
port Text
protocol Text
destHostname Word16
destPort Maybe Text
username Maybe Text
password = IO ProxyAddress -> m ProxyAddress
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ProxyAddress -> m ProxyAddress)
-> IO ProxyAddress -> m ProxyAddress
forall a b. (a -> b) -> a -> b
$ do
    Ptr InetAddress
inetaddr' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
inetaddr
    CString
protocol' <- Text -> IO CString
textToCString Text
protocol
    CString
destHostname' <- Text -> IO CString
textToCString Text
destHostname
    CString
maybeUsername <- case Maybe Text
username of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jUsername -> do
            CString
jUsername' <- Text -> IO CString
textToCString Text
jUsername
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jUsername'
    CString
maybePassword <- case Maybe Text
password of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jPassword -> do
            CString
jPassword' <- Text -> IO CString
textToCString Text
jPassword
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jPassword'
    Ptr ProxyAddress
result <- Ptr InetAddress
-> Word16
-> CString
-> CString
-> Word16
-> CString
-> CString
-> IO (Ptr ProxyAddress)
g_proxy_address_new Ptr InetAddress
inetaddr' Word16
port CString
protocol' CString
destHostname' Word16
destPort CString
maybeUsername CString
maybePassword
    Text -> Ptr ProxyAddress -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyAddressNew" Ptr ProxyAddress
result
    ProxyAddress
result' <- ((ManagedPtr ProxyAddress -> ProxyAddress)
-> Ptr ProxyAddress -> IO ProxyAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ProxyAddress -> ProxyAddress
ProxyAddress) Ptr ProxyAddress
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
inetaddr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
protocol'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
destHostname'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeUsername
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePassword
    ProxyAddress -> IO ProxyAddress
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ProxyAddress
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "g_proxy_address_get_destination_hostname" g_proxy_address_get_destination_hostname :: 
    Ptr ProxyAddress ->                     -- proxy : TInterface (Name {namespace = "Gio", name = "ProxyAddress"})
    IO CString

-- | Gets /@proxy@/\'s destination hostname; that is, the name of the host
-- that will be connected to via the proxy, not the name of the proxy
-- itself.
-- 
-- /Since: 2.26/
proxyAddressGetDestinationHostname ::
    (B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
    a
    -- ^ /@proxy@/: a t'GI.Gio.Objects.ProxyAddress.ProxyAddress'
    -> m T.Text
    -- ^ __Returns:__ the /@proxy@/\'s destination hostname
proxyAddressGetDestinationHostname :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m Text
proxyAddressGetDestinationHostname a
proxy = 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 ProxyAddress
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr ProxyAddress -> IO CString
g_proxy_address_get_destination_hostname Ptr ProxyAddress
proxy'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyAddressGetDestinationHostname" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetDestinationHostnameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetDestinationHostnameMethodInfo a signature where
    overloadedMethod = proxyAddressGetDestinationHostname

instance O.OverloadedMethodInfo ProxyAddressGetDestinationHostnameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddress.proxyAddressGetDestinationHostname",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ProxyAddress.html#v:proxyAddressGetDestinationHostname"
        })


#endif

-- method ProxyAddress::get_destination_port
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ProxyAddress" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GProxyAddress" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt16)
-- throws : False
-- Skip return : False

foreign import ccall "g_proxy_address_get_destination_port" g_proxy_address_get_destination_port :: 
    Ptr ProxyAddress ->                     -- proxy : TInterface (Name {namespace = "Gio", name = "ProxyAddress"})
    IO Word16

-- | Gets /@proxy@/\'s destination port; that is, the port on the
-- destination host that will be connected to via the proxy, not the
-- port number of the proxy itself.
-- 
-- /Since: 2.26/
proxyAddressGetDestinationPort ::
    (B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
    a
    -- ^ /@proxy@/: a t'GI.Gio.Objects.ProxyAddress.ProxyAddress'
    -> m Word16
    -- ^ __Returns:__ the /@proxy@/\'s destination port
proxyAddressGetDestinationPort :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m Word16
proxyAddressGetDestinationPort a
proxy = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ do
    Ptr ProxyAddress
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Word16
result <- Ptr ProxyAddress -> IO Word16
g_proxy_address_get_destination_port Ptr ProxyAddress
proxy'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
result

#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetDestinationPortMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetDestinationPortMethodInfo a signature where
    overloadedMethod = proxyAddressGetDestinationPort

instance O.OverloadedMethodInfo ProxyAddressGetDestinationPortMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddress.proxyAddressGetDestinationPort",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ProxyAddress.html#v:proxyAddressGetDestinationPort"
        })


#endif

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

foreign import ccall "g_proxy_address_get_destination_protocol" g_proxy_address_get_destination_protocol :: 
    Ptr ProxyAddress ->                     -- proxy : TInterface (Name {namespace = "Gio", name = "ProxyAddress"})
    IO CString

-- | Gets the protocol that is being spoken to the destination
-- server; eg, \"http\" or \"ftp\".
-- 
-- /Since: 2.34/
proxyAddressGetDestinationProtocol ::
    (B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
    a
    -- ^ /@proxy@/: a t'GI.Gio.Objects.ProxyAddress.ProxyAddress'
    -> m T.Text
    -- ^ __Returns:__ the /@proxy@/\'s destination protocol
proxyAddressGetDestinationProtocol :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m Text
proxyAddressGetDestinationProtocol a
proxy = 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 ProxyAddress
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr ProxyAddress -> IO CString
g_proxy_address_get_destination_protocol Ptr ProxyAddress
proxy'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyAddressGetDestinationProtocol" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetDestinationProtocolMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetDestinationProtocolMethodInfo a signature where
    overloadedMethod = proxyAddressGetDestinationProtocol

instance O.OverloadedMethodInfo ProxyAddressGetDestinationProtocolMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddress.proxyAddressGetDestinationProtocol",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ProxyAddress.html#v:proxyAddressGetDestinationProtocol"
        })


#endif

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

foreign import ccall "g_proxy_address_get_password" g_proxy_address_get_password :: 
    Ptr ProxyAddress ->                     -- proxy : TInterface (Name {namespace = "Gio", name = "ProxyAddress"})
    IO CString

-- | Gets /@proxy@/\'s password.
-- 
-- /Since: 2.26/
proxyAddressGetPassword ::
    (B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
    a
    -- ^ /@proxy@/: a t'GI.Gio.Objects.ProxyAddress.ProxyAddress'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the /@proxy@/\'s password
proxyAddressGetPassword :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m (Maybe Text)
proxyAddressGetPassword a
proxy = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr ProxyAddress
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr ProxyAddress -> IO CString
g_proxy_address_get_password Ptr ProxyAddress
proxy'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetPasswordMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetPasswordMethodInfo a signature where
    overloadedMethod = proxyAddressGetPassword

instance O.OverloadedMethodInfo ProxyAddressGetPasswordMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddress.proxyAddressGetPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ProxyAddress.html#v:proxyAddressGetPassword"
        })


#endif

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

foreign import ccall "g_proxy_address_get_protocol" g_proxy_address_get_protocol :: 
    Ptr ProxyAddress ->                     -- proxy : TInterface (Name {namespace = "Gio", name = "ProxyAddress"})
    IO CString

-- | Gets /@proxy@/\'s protocol. eg, \"socks\" or \"http\"
-- 
-- /Since: 2.26/
proxyAddressGetProtocol ::
    (B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
    a
    -- ^ /@proxy@/: a t'GI.Gio.Objects.ProxyAddress.ProxyAddress'
    -> m T.Text
    -- ^ __Returns:__ the /@proxy@/\'s protocol
proxyAddressGetProtocol :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m Text
proxyAddressGetProtocol a
proxy = 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 ProxyAddress
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr ProxyAddress -> IO CString
g_proxy_address_get_protocol Ptr ProxyAddress
proxy'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyAddressGetProtocol" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetProtocolMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetProtocolMethodInfo a signature where
    overloadedMethod = proxyAddressGetProtocol

instance O.OverloadedMethodInfo ProxyAddressGetProtocolMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddress.proxyAddressGetProtocol",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ProxyAddress.html#v:proxyAddressGetProtocol"
        })


#endif

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

foreign import ccall "g_proxy_address_get_uri" g_proxy_address_get_uri :: 
    Ptr ProxyAddress ->                     -- proxy : TInterface (Name {namespace = "Gio", name = "ProxyAddress"})
    IO CString

-- | Gets the proxy URI that /@proxy@/ was constructed from.
-- 
-- /Since: 2.34/
proxyAddressGetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
    a
    -- ^ /@proxy@/: a t'GI.Gio.Objects.ProxyAddress.ProxyAddress'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the /@proxy@/\'s URI, or 'P.Nothing' if unknown
proxyAddressGetUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m (Maybe Text)
proxyAddressGetUri a
proxy = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr ProxyAddress
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr ProxyAddress -> IO CString
g_proxy_address_get_uri Ptr ProxyAddress
proxy'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetUriMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetUriMethodInfo a signature where
    overloadedMethod = proxyAddressGetUri

instance O.OverloadedMethodInfo ProxyAddressGetUriMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddress.proxyAddressGetUri",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ProxyAddress.html#v:proxyAddressGetUri"
        })


#endif

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

foreign import ccall "g_proxy_address_get_username" g_proxy_address_get_username :: 
    Ptr ProxyAddress ->                     -- proxy : TInterface (Name {namespace = "Gio", name = "ProxyAddress"})
    IO CString

-- | Gets /@proxy@/\'s username.
-- 
-- /Since: 2.26/
proxyAddressGetUsername ::
    (B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
    a
    -- ^ /@proxy@/: a t'GI.Gio.Objects.ProxyAddress.ProxyAddress'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the /@proxy@/\'s username
proxyAddressGetUsername :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m (Maybe Text)
proxyAddressGetUsername a
proxy = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr ProxyAddress
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    CString
result <- Ptr ProxyAddress -> IO CString
g_proxy_address_get_username Ptr ProxyAddress
proxy'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetUsernameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetUsernameMethodInfo a signature where
    overloadedMethod = proxyAddressGetUsername

instance O.OverloadedMethodInfo ProxyAddressGetUsernameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ProxyAddress.proxyAddressGetUsername",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ProxyAddress.html#v:proxyAddressGetUsername"
        })


#endif