{-# 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
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
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddressEnumerator as Gio.SocketAddressEnumerator
#else
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
#endif
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
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 :: (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
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 <- 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 /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject ProxyAddress ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveProxyAddressMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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 :: ProxyAddress -> p
fromLabel = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
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 :: ProxyAddress -> p
getField = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
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 :: MethodProxy info ProxyAddress
fromLabel = MethodProxy info ProxyAddress
forall info obj. MethodProxy info obj
O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
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"
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 :: forall o.
AttrBaseTypeConstraint
ProxyAddressDestinationHostnamePropertyInfo o =>
o -> IO (AttrGetType ProxyAddressDestinationHostnamePropertyInfo)
attrGet = o -> IO Text
o -> IO (AttrGetType ProxyAddressDestinationHostnamePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m Text
getProxyAddressDestinationHostname
attrSet :: forall o b.
(AttrBaseTypeConstraint
ProxyAddressDestinationHostnamePropertyInfo o,
AttrSetTypeConstraint
ProxyAddressDestinationHostnamePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
ProxyAddressDestinationHostnamePropertyInfo o,
AttrTransferTypeConstraint
ProxyAddressDestinationHostnamePropertyInfo b) =>
Proxy o
-> b
-> IO
(AttrTransferType ProxyAddressDestinationHostnamePropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
ProxyAddressDestinationHostnamePropertyInfo o,
AttrSetTypeConstraint
ProxyAddressDestinationHostnamePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressDestinationHostname
attrClear :: forall o.
AttrBaseTypeConstraint
ProxyAddressDestinationHostnamePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.destinationHostname"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#g:attr:destinationHostname"
})
#endif
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"
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 :: forall o.
AttrBaseTypeConstraint ProxyAddressDestinationPortPropertyInfo o =>
o -> IO (AttrGetType ProxyAddressDestinationPortPropertyInfo)
attrGet = o -> IO Word32
o -> IO (AttrGetType ProxyAddressDestinationPortPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m Word32
getProxyAddressDestinationPort
attrSet :: forall o b.
(AttrBaseTypeConstraint ProxyAddressDestinationPortPropertyInfo o,
AttrSetTypeConstraint ProxyAddressDestinationPortPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint ProxyAddressDestinationPortPropertyInfo o,
AttrTransferTypeConstraint
ProxyAddressDestinationPortPropertyInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType ProxyAddressDestinationPortPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint ProxyAddressDestinationPortPropertyInfo o,
AttrSetTypeConstraint ProxyAddressDestinationPortPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Word32 -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructProxyAddressDestinationPort
attrClear :: forall o.
AttrBaseTypeConstraint ProxyAddressDestinationPortPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.destinationPort"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#g:attr:destinationPort"
})
#endif
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"
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 :: forall o.
AttrBaseTypeConstraint
ProxyAddressDestinationProtocolPropertyInfo o =>
o -> IO (AttrGetType ProxyAddressDestinationProtocolPropertyInfo)
attrGet = o -> IO Text
o -> IO (AttrGetType ProxyAddressDestinationProtocolPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m Text
getProxyAddressDestinationProtocol
attrSet :: forall o b.
(AttrBaseTypeConstraint
ProxyAddressDestinationProtocolPropertyInfo o,
AttrSetTypeConstraint
ProxyAddressDestinationProtocolPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint
ProxyAddressDestinationProtocolPropertyInfo o,
AttrTransferTypeConstraint
ProxyAddressDestinationProtocolPropertyInfo b) =>
Proxy o
-> b
-> IO
(AttrTransferType ProxyAddressDestinationProtocolPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint
ProxyAddressDestinationProtocolPropertyInfo o,
AttrSetTypeConstraint
ProxyAddressDestinationProtocolPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressDestinationProtocol
attrClear :: forall o.
AttrBaseTypeConstraint
ProxyAddressDestinationProtocolPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.destinationProtocol"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#g:attr:destinationProtocol"
})
#endif
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"
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 :: forall o.
AttrBaseTypeConstraint ProxyAddressPasswordPropertyInfo o =>
o -> IO (AttrGetType ProxyAddressPasswordPropertyInfo)
attrGet = o -> IO (Maybe Text)
o -> IO (AttrGetType ProxyAddressPasswordPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m (Maybe Text)
getProxyAddressPassword
attrSet :: forall o b.
(AttrBaseTypeConstraint ProxyAddressPasswordPropertyInfo o,
AttrSetTypeConstraint ProxyAddressPasswordPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint ProxyAddressPasswordPropertyInfo o,
AttrTransferTypeConstraint ProxyAddressPasswordPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType ProxyAddressPasswordPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint ProxyAddressPasswordPropertyInfo o,
AttrSetTypeConstraint ProxyAddressPasswordPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressPassword
attrClear :: forall o.
AttrBaseTypeConstraint ProxyAddressPasswordPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.password"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#g:attr:password"
})
#endif
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"
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 :: forall o.
AttrBaseTypeConstraint ProxyAddressProtocolPropertyInfo o =>
o -> IO (AttrGetType ProxyAddressProtocolPropertyInfo)
attrGet = o -> IO Text
o -> IO (AttrGetType ProxyAddressProtocolPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m Text
getProxyAddressProtocol
attrSet :: forall o b.
(AttrBaseTypeConstraint ProxyAddressProtocolPropertyInfo o,
AttrSetTypeConstraint ProxyAddressProtocolPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint ProxyAddressProtocolPropertyInfo o,
AttrTransferTypeConstraint ProxyAddressProtocolPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType ProxyAddressProtocolPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint ProxyAddressProtocolPropertyInfo o,
AttrSetTypeConstraint ProxyAddressProtocolPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressProtocol
attrClear :: forall o.
AttrBaseTypeConstraint ProxyAddressProtocolPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.protocol"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#g:attr:protocol"
})
#endif
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"
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 :: forall o.
AttrBaseTypeConstraint ProxyAddressUriPropertyInfo o =>
o -> IO (AttrGetType ProxyAddressUriPropertyInfo)
attrGet = o -> IO (Maybe Text)
o -> IO (AttrGetType ProxyAddressUriPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m (Maybe Text)
getProxyAddressUri
attrSet :: forall o b.
(AttrBaseTypeConstraint ProxyAddressUriPropertyInfo o,
AttrSetTypeConstraint ProxyAddressUriPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint ProxyAddressUriPropertyInfo o,
AttrTransferTypeConstraint ProxyAddressUriPropertyInfo b) =>
Proxy o -> b -> IO (AttrTransferType ProxyAddressUriPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint ProxyAddressUriPropertyInfo o,
AttrSetTypeConstraint ProxyAddressUriPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressUri
attrClear :: forall o.
AttrBaseTypeConstraint ProxyAddressUriPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.uri"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#g:attr:uri"
})
#endif
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"
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 :: forall o.
AttrBaseTypeConstraint ProxyAddressUsernamePropertyInfo o =>
o -> IO (AttrGetType ProxyAddressUsernamePropertyInfo)
attrGet = o -> IO (Maybe Text)
o -> IO (AttrGetType ProxyAddressUsernamePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsProxyAddress o) =>
o -> m (Maybe Text)
getProxyAddressUsername
attrSet :: forall o b.
(AttrBaseTypeConstraint ProxyAddressUsernamePropertyInfo o,
AttrSetTypeConstraint ProxyAddressUsernamePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint ProxyAddressUsernamePropertyInfo o,
AttrTransferTypeConstraint ProxyAddressUsernamePropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType ProxyAddressUsernamePropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint ProxyAddressUsernamePropertyInfo o,
AttrSetTypeConstraint ProxyAddressUsernamePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsProxyAddress o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructProxyAddressUsername
attrClear :: forall o.
AttrBaseTypeConstraint ProxyAddressUsernamePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.username"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
proxyAddressDestinationHostname :: AttrLabelProxy "destinationHostname"
proxyAddressDestinationHostname :: AttrLabelProxy "destinationHostname"
proxyAddressDestinationHostname = AttrLabelProxy "destinationHostname"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
proxyAddressDestinationPort :: AttrLabelProxy "destinationPort"
proxyAddressDestinationPort :: AttrLabelProxy "destinationPort"
proxyAddressDestinationPort = AttrLabelProxy "destinationPort"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
proxyAddressDestinationProtocol :: AttrLabelProxy "destinationProtocol"
proxyAddressDestinationProtocol :: AttrLabelProxy "destinationProtocol"
proxyAddressDestinationProtocol = AttrLabelProxy "destinationProtocol"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
proxyAddressPassword :: AttrLabelProxy "password"
proxyAddressPassword :: AttrLabelProxy "password"
proxyAddressPassword = AttrLabelProxy "password"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
proxyAddressProtocol :: AttrLabelProxy "protocol"
proxyAddressProtocol :: AttrLabelProxy "protocol"
proxyAddressProtocol = AttrLabelProxy "protocol"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
proxyAddressUri :: AttrLabelProxy "uri"
proxyAddressUri :: AttrLabelProxy "uri"
proxyAddressUri = AttrLabelProxy "uri"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
proxyAddressUsername :: AttrLabelProxy "username"
proxyAddressUsername :: AttrLabelProxy "username"
proxyAddressUsername = AttrLabelProxy "username"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ProxyAddress = ProxyAddressSignalList
type ProxyAddressSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#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 :: 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
inetaddr' <- a -> IO (Ptr InetAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
inetaddr
protocol' <- textToCString protocol
destHostname' <- textToCString destHostname
maybeUsername <- case 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
FP.nullPtr
Just Text
jUsername -> do
jUsername' <- Text -> IO CString
textToCString Text
jUsername
return jUsername'
maybePassword <- case 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
FP.nullPtr
Just Text
jPassword -> do
jPassword' <- Text -> IO CString
textToCString Text
jPassword
return jPassword'
result <- g_proxy_address_new inetaddr' port protocol' destHostname' destPort maybeUsername maybePassword
checkUnexpectedReturnNULL "proxyAddressNew" result
result' <- (wrapObject ProxyAddress) result
touchManagedPtr inetaddr
freeMem protocol'
freeMem destHostname'
freeMem maybeUsername
freeMem maybePassword
return 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 :: 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
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
result <- g_proxy_address_get_destination_hostname proxy'
checkUnexpectedReturnNULL "proxyAddressGetDestinationHostname" result
result' <- cstringToText result
touchManagedPtr proxy
return result'
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetDestinationHostnameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetDestinationHostnameMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m Text
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m Text
proxyAddressGetDestinationHostname
instance O.OverloadedMethodInfo ProxyAddressGetDestinationHostnameMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.proxyAddressGetDestinationHostname",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#v: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 :: 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
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
result <- g_proxy_address_get_destination_port proxy'
touchManagedPtr proxy
return result
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetDestinationPortMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetDestinationPortMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m Word16
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m Word16
proxyAddressGetDestinationPort
instance O.OverloadedMethodInfo ProxyAddressGetDestinationPortMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.proxyAddressGetDestinationPort",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#v: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 :: 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
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
result <- g_proxy_address_get_destination_protocol proxy'
checkUnexpectedReturnNULL "proxyAddressGetDestinationProtocol" result
result' <- cstringToText result
touchManagedPtr proxy
return result'
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetDestinationProtocolMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetDestinationProtocolMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m Text
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m Text
proxyAddressGetDestinationProtocol
instance O.OverloadedMethodInfo ProxyAddressGetDestinationProtocolMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.proxyAddressGetDestinationProtocol",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#v: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 (Maybe T.Text)
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
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
result <- g_proxy_address_get_password proxy'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
return result''
touchManagedPtr proxy
return maybeResult
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetPasswordMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetPasswordMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe Text)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m (Maybe Text)
proxyAddressGetPassword
instance O.OverloadedMethodInfo ProxyAddressGetPasswordMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.proxyAddressGetPassword",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#v: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 :: 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
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
result <- g_proxy_address_get_protocol proxy'
checkUnexpectedReturnNULL "proxyAddressGetProtocol" result
result' <- cstringToText result
touchManagedPtr proxy
return result'
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetProtocolMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetProtocolMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m Text
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m Text
proxyAddressGetProtocol
instance O.OverloadedMethodInfo ProxyAddressGetProtocolMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.proxyAddressGetProtocol",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#v: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 (Maybe T.Text)
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
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
result <- g_proxy_address_get_uri proxy'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
return result''
touchManagedPtr proxy
return maybeResult
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetUriMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetUriMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe Text)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m (Maybe Text)
proxyAddressGetUri
instance O.OverloadedMethodInfo ProxyAddressGetUriMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.proxyAddressGetUri",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#v: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 (Maybe T.Text)
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
proxy' <- a -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
result <- g_proxy_address_get_username proxy'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
return result''
touchManagedPtr proxy
return maybeResult
#if defined(ENABLE_OVERLOADING)
data ProxyAddressGetUsernameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsProxyAddress a) => O.OverloadedMethod ProxyAddressGetUsernameMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m (Maybe Text)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsProxyAddress a) =>
a -> m (Maybe Text)
proxyAddressGetUsername
instance O.OverloadedMethodInfo ProxyAddressGetUsernameMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.ProxyAddress.proxyAddressGetUsername",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-ProxyAddress.html#v:proxyAddressGetUsername"
})
#endif