{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.ProxyAddress
(
ProxyAddress(..) ,
IsProxyAddress ,
toProxyAddress ,
#if defined(ENABLE_OVERLOADING)
ResolveProxyAddressMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressGetDestinationHostnameMethodInfo,
#endif
proxyAddressGetDestinationHostname ,
#if defined(ENABLE_OVERLOADING)
ProxyAddressGetDestinationPortMethodInfo,
#endif
proxyAddressGetDestinationPort ,
#if defined(ENABLE_OVERLOADING)
ProxyAddressGetDestinationProtocolMethodInfo,
#endif
proxyAddressGetDestinationProtocol ,
#if defined(ENABLE_OVERLOADING)
ProxyAddressGetPasswordMethodInfo ,
#endif
proxyAddressGetPassword ,
#if defined(ENABLE_OVERLOADING)
ProxyAddressGetProtocolMethodInfo ,
#endif
proxyAddressGetProtocol ,
#if defined(ENABLE_OVERLOADING)
ProxyAddressGetUriMethodInfo ,
#endif
proxyAddressGetUri ,
#if defined(ENABLE_OVERLOADING)
ProxyAddressGetUsernameMethodInfo ,
#endif
proxyAddressGetUsername ,
proxyAddressNew ,
#if defined(ENABLE_OVERLOADING)
ProxyAddressDestinationHostnamePropertyInfo,
#endif
constructProxyAddressDestinationHostname,
getProxyAddressDestinationHostname ,
#if defined(ENABLE_OVERLOADING)
proxyAddressDestinationHostname ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressDestinationPortPropertyInfo ,
#endif
constructProxyAddressDestinationPort ,
getProxyAddressDestinationPort ,
#if defined(ENABLE_OVERLOADING)
proxyAddressDestinationPort ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressDestinationProtocolPropertyInfo,
#endif
constructProxyAddressDestinationProtocol,
getProxyAddressDestinationProtocol ,
#if defined(ENABLE_OVERLOADING)
proxyAddressDestinationProtocol ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressPasswordPropertyInfo ,
#endif
constructProxyAddressPassword ,
getProxyAddressPassword ,
#if defined(ENABLE_OVERLOADING)
proxyAddressPassword ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressProtocolPropertyInfo ,
#endif
constructProxyAddressProtocol ,
getProxyAddressProtocol ,
#if defined(ENABLE_OVERLOADING)
proxyAddressProtocol ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyAddressUriPropertyInfo ,
#endif
constructProxyAddressUri ,
getProxyAddressUri ,
#if defined(ENABLE_OVERLOADING)
proxyAddressUri ,
#endif
#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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.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.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
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
/= :: ProxyAddress -> ProxyAddress -> Bool
$c/= :: ProxyAddress -> ProxyAddress -> Bool
== :: ProxyAddress -> ProxyAddress -> Bool
$c== :: 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
instance B.GValue.IsGValue ProxyAddress where
toGValue :: ProxyAddress -> IO GValue
toGValue ProxyAddress
o = do
GType
gtype <- IO GType
c_g_proxy_address_get_type
ProxyAddress -> (Ptr ProxyAddress -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ProxyAddress
o (GType
-> (GValue -> Ptr ProxyAddress -> IO ())
-> Ptr ProxyAddress
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ProxyAddress -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO ProxyAddress
fromGValue GValue
gv = do
Ptr ProxyAddress
ptr <- GValue -> IO (Ptr ProxyAddress)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ProxyAddress)
(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
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]
toProxyAddress :: (MonadIO m, IsProxyAddress o) => o -> m ProxyAddress
toProxyAddress :: o -> m ProxyAddress
toProxyAddress = IO ProxyAddress -> m ProxyAddress
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr ProxyAddress -> ProxyAddress
ProxyAddress
#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.MethodInfo 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
#endif
getProxyAddressDestinationHostname :: (MonadIO m, IsProxyAddress o) => o -> m T.Text
getProxyAddressDestinationHostname :: o -> m Text
getProxyAddressDestinationHostname o
obj = IO Text -> m Text
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
$ 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"
constructProxyAddressDestinationHostname :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressDestinationHostname :: Text -> m (GValueConstruct o)
constructProxyAddressDestinationHostname Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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
#endif
getProxyAddressDestinationPort :: (MonadIO m, IsProxyAddress o) => o -> m Word32
getProxyAddressDestinationPort :: o -> m Word32
getProxyAddressDestinationPort 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 String
"destination-port"
constructProxyAddressDestinationPort :: (IsProxyAddress o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructProxyAddressDestinationPort :: Word32 -> m (GValueConstruct o)
constructProxyAddressDestinationPort Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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
#endif
getProxyAddressDestinationProtocol :: (MonadIO m, IsProxyAddress o) => o -> m T.Text
getProxyAddressDestinationProtocol :: o -> m Text
getProxyAddressDestinationProtocol o
obj = IO Text -> m Text
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
$ 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"
constructProxyAddressDestinationProtocol :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressDestinationProtocol :: Text -> m (GValueConstruct o)
constructProxyAddressDestinationProtocol Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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
#endif
getProxyAddressPassword :: (MonadIO m, IsProxyAddress o) => o -> m T.Text
getProxyAddressPassword :: o -> m Text
getProxyAddressPassword o
obj = IO Text -> m Text
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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getProxyAddressPassword" (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
"password"
constructProxyAddressPassword :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressPassword :: Text -> m (GValueConstruct o)
constructProxyAddressPassword Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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 = T.Text
type AttrLabel ProxyAddressPasswordPropertyInfo = "password"
type AttrOrigin ProxyAddressPasswordPropertyInfo = ProxyAddress
attrGet = getProxyAddressPassword
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructProxyAddressPassword
attrClear = undefined
#endif
getProxyAddressProtocol :: (MonadIO m, IsProxyAddress o) => o -> m T.Text
getProxyAddressProtocol :: o -> m Text
getProxyAddressProtocol o
obj = IO Text -> m Text
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
$ 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"
constructProxyAddressProtocol :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressProtocol :: Text -> m (GValueConstruct o)
constructProxyAddressProtocol Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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
#endif
getProxyAddressUri :: (MonadIO m, IsProxyAddress o) => o -> m T.Text
getProxyAddressUri :: o -> m Text
getProxyAddressUri o
obj = IO Text -> m Text
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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getProxyAddressUri" (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
"uri"
constructProxyAddressUri :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressUri :: Text -> m (GValueConstruct o)
constructProxyAddressUri Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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 = T.Text
type AttrLabel ProxyAddressUriPropertyInfo = "uri"
type AttrOrigin ProxyAddressUriPropertyInfo = ProxyAddress
attrGet = getProxyAddressUri
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructProxyAddressUri
attrClear = undefined
#endif
getProxyAddressUsername :: (MonadIO m, IsProxyAddress o) => o -> m T.Text
getProxyAddressUsername :: o -> m Text
getProxyAddressUsername o
obj = IO Text -> m Text
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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getProxyAddressUsername" (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
"username"
constructProxyAddressUsername :: (IsProxyAddress o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructProxyAddressUsername :: Text -> m (GValueConstruct o)
constructProxyAddressUsername Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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 = T.Text
type AttrLabel ProxyAddressUsernamePropertyInfo = "username"
type AttrOrigin ProxyAddressUsernamePropertyInfo = ProxyAddress
attrGet = getProxyAddressUsername
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructProxyAddressUsername
attrClear = undefined
#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
foreign import ccall "g_proxy_address_new" g_proxy_address_new ::
Ptr Gio.InetAddress.InetAddress ->
Word16 ->
CString ->
CString ->
Word16 ->
CString ->
CString ->
IO (Ptr ProxyAddress)
proxyAddressNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.InetAddress.IsInetAddress a) =>
a
-> Word16
-> T.Text
-> T.Text
-> Word16
-> Maybe (T.Text)
-> Maybe (T.Text)
-> m ProxyAddress
proxyAddressNew :: 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 (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 (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 (m :: * -> *) a. Monad m => a -> m a
return CString
jUsername'
CString
maybePassword <- case Maybe Text
password of
Maybe Text
Nothing -> CString -> IO CString
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 (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 (m :: * -> *) a. Monad m => a -> m a
return ProxyAddress
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_proxy_address_get_destination_hostname" g_proxy_address_get_destination_hostname ::
Ptr ProxyAddress ->
IO CString
proxyAddressGetDestinationHostname ::
(B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
a
-> m T.Text
proxyAddressGetDestinationHostname :: a -> m Text
proxyAddressGetDestinationHostname a
proxy = IO Text -> m Text
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 (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.MethodInfo ProxyAddressGetDestinationHostnameMethodInfo a signature where
overloadedMethod = proxyAddressGetDestinationHostname
#endif
foreign import ccall "g_proxy_address_get_destination_port" g_proxy_address_get_destination_port ::
Ptr ProxyAddress ->
IO Word16
proxyAddressGetDestinationPort ::
(B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
a
-> m Word16
proxyAddressGetDestinationPort :: a -> m Word16
proxyAddressGetDestinationPort a
proxy = IO Word16 -> m Word16
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 (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.MethodInfo ProxyAddressGetDestinationPortMethodInfo a signature where
overloadedMethod = proxyAddressGetDestinationPort
#endif
foreign import ccall "g_proxy_address_get_destination_protocol" g_proxy_address_get_destination_protocol ::
Ptr ProxyAddress ->
IO CString
proxyAddressGetDestinationProtocol ::
(B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
a
-> m T.Text
proxyAddressGetDestinationProtocol :: a -> m Text
proxyAddressGetDestinationProtocol a
proxy = IO Text -> m Text
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 (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.MethodInfo ProxyAddressGetDestinationProtocolMethodInfo a signature where
overloadedMethod = proxyAddressGetDestinationProtocol
#endif
foreign import ccall "g_proxy_address_get_password" g_proxy_address_get_password ::
Ptr ProxyAddress ->
IO CString
proxyAddressGetPassword ::
(B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
a
-> m T.Text
proxyAddressGetPassword :: a -> m Text
proxyAddressGetPassword a
proxy = IO Text -> m Text
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_password Ptr ProxyAddress
proxy'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyAddressGetPassword" 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 (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetPasswordMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.MethodInfo ProxyAddressGetPasswordMethodInfo a signature where
overloadedMethod = proxyAddressGetPassword
#endif
foreign import ccall "g_proxy_address_get_protocol" g_proxy_address_get_protocol ::
Ptr ProxyAddress ->
IO CString
proxyAddressGetProtocol ::
(B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
a
-> m T.Text
proxyAddressGetProtocol :: a -> m Text
proxyAddressGetProtocol a
proxy = IO Text -> m Text
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 (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.MethodInfo ProxyAddressGetProtocolMethodInfo a signature where
overloadedMethod = proxyAddressGetProtocol
#endif
foreign import ccall "g_proxy_address_get_uri" g_proxy_address_get_uri ::
Ptr ProxyAddress ->
IO CString
proxyAddressGetUri ::
(B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
a
-> m T.Text
proxyAddressGetUri :: a -> m Text
proxyAddressGetUri a
proxy = IO Text -> m Text
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_uri Ptr ProxyAddress
proxy'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyAddressGetUri" 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 (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetUriMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.MethodInfo ProxyAddressGetUriMethodInfo a signature where
overloadedMethod = proxyAddressGetUri
#endif
foreign import ccall "g_proxy_address_get_username" g_proxy_address_get_username ::
Ptr ProxyAddress ->
IO CString
proxyAddressGetUsername ::
(B.CallStack.HasCallStack, MonadIO m, IsProxyAddress a) =>
a
-> m T.Text
proxyAddressGetUsername :: a -> m Text
proxyAddressGetUsername a
proxy = IO Text -> m Text
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_username Ptr ProxyAddress
proxy'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyAddressGetUsername" 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 (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetUsernameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.MethodInfo ProxyAddressGetUsernameMethodInfo a signature where
overloadedMethod = proxyAddressGetUsername
#endif