{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.Proxy
(
Proxy(..) ,
IsProxy ,
toProxy ,
#if defined(ENABLE_OVERLOADING)
ResolveProxyMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ProxyConnectMethodInfo ,
#endif
proxyConnect ,
#if defined(ENABLE_OVERLOADING)
ProxyConnectAsyncMethodInfo ,
#endif
proxyConnectAsync ,
#if defined(ENABLE_OVERLOADING)
ProxyConnectFinishMethodInfo ,
#endif
proxyConnectFinish ,
proxyGetDefaultForProtocol ,
#if defined(ENABLE_OVERLOADING)
ProxySupportsHostnameMethodInfo ,
#endif
proxySupportsHostname ,
) 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 qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.ProxyAddress as Gio.ProxyAddress
newtype Proxy = Proxy (SP.ManagedPtr Proxy)
deriving (Proxy -> Proxy -> Bool
(Proxy -> Proxy -> Bool) -> (Proxy -> Proxy -> Bool) -> Eq Proxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Proxy -> Proxy -> Bool
$c/= :: Proxy -> Proxy -> Bool
== :: Proxy -> Proxy -> Bool
$c== :: Proxy -> Proxy -> Bool
Eq)
instance SP.ManagedPtrNewtype Proxy where
toManagedPtr :: Proxy -> ManagedPtr Proxy
toManagedPtr (Proxy ManagedPtr Proxy
p) = ManagedPtr Proxy
p
foreign import ccall "g_proxy_get_type"
c_g_proxy_get_type :: IO B.Types.GType
instance B.Types.TypedObject Proxy where
glibType :: IO GType
glibType = IO GType
c_g_proxy_get_type
instance B.Types.GObject Proxy
instance B.GValue.IsGValue Proxy where
toGValue :: Proxy -> IO GValue
toGValue Proxy
o = do
GType
gtype <- IO GType
c_g_proxy_get_type
Proxy -> (Ptr Proxy -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Proxy
o (GType -> (GValue -> Ptr Proxy -> IO ()) -> Ptr Proxy -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Proxy -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Proxy
fromGValue GValue
gv = do
Ptr Proxy
ptr <- GValue -> IO (Ptr Proxy)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Proxy)
(ManagedPtr Proxy -> Proxy) -> Ptr Proxy -> IO Proxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Proxy -> Proxy
Proxy Ptr Proxy
ptr
class (SP.GObject o, O.IsDescendantOf Proxy o) => IsProxy o
instance (SP.GObject o, O.IsDescendantOf Proxy o) => IsProxy o
instance O.HasParentTypes Proxy
type instance O.ParentTypes Proxy = '[GObject.Object.Object]
toProxy :: (MonadIO m, IsProxy o) => o -> m Proxy
toProxy :: o -> m Proxy
toProxy = IO Proxy -> m Proxy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Proxy -> m Proxy) -> (o -> IO Proxy) -> o -> m Proxy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Proxy -> Proxy) -> o -> IO Proxy
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Proxy -> Proxy
Proxy
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Proxy
type instance O.AttributeList Proxy = ProxyAttributeList
type ProxyAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveProxyMethod (t :: Symbol) (o :: *) :: * where
ResolveProxyMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveProxyMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveProxyMethod "connect" o = ProxyConnectMethodInfo
ResolveProxyMethod "connectAsync" o = ProxyConnectAsyncMethodInfo
ResolveProxyMethod "connectFinish" o = ProxyConnectFinishMethodInfo
ResolveProxyMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveProxyMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveProxyMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveProxyMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveProxyMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveProxyMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveProxyMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveProxyMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveProxyMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveProxyMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveProxyMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveProxyMethod "supportsHostname" o = ProxySupportsHostnameMethodInfo
ResolveProxyMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveProxyMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveProxyMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveProxyMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveProxyMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveProxyMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveProxyMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveProxyMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveProxyMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveProxyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveProxyMethod t Proxy, O.MethodInfo info Proxy p) => OL.IsLabel t (Proxy -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "g_proxy_connect" g_proxy_connect ::
Ptr Proxy ->
Ptr Gio.IOStream.IOStream ->
Ptr Gio.ProxyAddress.ProxyAddress ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO (Ptr Gio.IOStream.IOStream)
proxyConnect ::
(B.CallStack.HasCallStack, MonadIO m, IsProxy a, Gio.IOStream.IsIOStream b, Gio.ProxyAddress.IsProxyAddress c, Gio.Cancellable.IsCancellable d) =>
a
-> b
-> c
-> Maybe (d)
-> m Gio.IOStream.IOStream
proxyConnect :: a -> b -> c -> Maybe d -> m IOStream
proxyConnect a
proxy b
connection c
proxyAddress Maybe d
cancellable = IO IOStream -> m IOStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOStream -> m IOStream) -> IO IOStream -> m IOStream
forall a b. (a -> b) -> a -> b
$ do
Ptr Proxy
proxy' <- a -> IO (Ptr Proxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
Ptr IOStream
connection' <- b -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
connection
Ptr ProxyAddress
proxyAddress' <- c -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
proxyAddress
Ptr Cancellable
maybeCancellable <- case Maybe d
cancellable of
Maybe d
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just d
jCancellable -> do
Ptr Cancellable
jCancellable' <- d -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr d
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO IOStream -> IO () -> IO IOStream
forall a b. IO a -> IO b -> IO a
onException (do
Ptr IOStream
result <- (Ptr (Ptr GError) -> IO (Ptr IOStream)) -> IO (Ptr IOStream)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr IOStream)) -> IO (Ptr IOStream))
-> (Ptr (Ptr GError) -> IO (Ptr IOStream)) -> IO (Ptr IOStream)
forall a b. (a -> b) -> a -> b
$ Ptr Proxy
-> Ptr IOStream
-> Ptr ProxyAddress
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr IOStream)
g_proxy_connect Ptr Proxy
proxy' Ptr IOStream
connection' Ptr ProxyAddress
proxyAddress' Ptr Cancellable
maybeCancellable
Text -> Ptr IOStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyConnect" Ptr IOStream
result
IOStream
result' <- ((ManagedPtr IOStream -> IOStream) -> Ptr IOStream -> IO IOStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr IOStream -> IOStream
Gio.IOStream.IOStream) Ptr IOStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
connection
c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
proxyAddress
Maybe d -> (d -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe d
cancellable d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
IOStream -> IO IOStream
forall (m :: * -> *) a. Monad m => a -> m a
return IOStream
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data ProxyConnectMethodInfo
instance (signature ~ (b -> c -> Maybe (d) -> m Gio.IOStream.IOStream), MonadIO m, IsProxy a, Gio.IOStream.IsIOStream b, Gio.ProxyAddress.IsProxyAddress c, Gio.Cancellable.IsCancellable d) => O.MethodInfo ProxyConnectMethodInfo a signature where
overloadedMethod = proxyConnect
#endif
foreign import ccall "g_proxy_connect_async" g_proxy_connect_async ::
Ptr Proxy ->
Ptr Gio.IOStream.IOStream ->
Ptr Gio.ProxyAddress.ProxyAddress ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
proxyConnectAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsProxy a, Gio.IOStream.IsIOStream b, Gio.ProxyAddress.IsProxyAddress c, Gio.Cancellable.IsCancellable d) =>
a
-> b
-> c
-> Maybe (d)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
proxyConnectAsync :: a -> b -> c -> Maybe d -> Maybe AsyncReadyCallback -> m ()
proxyConnectAsync a
proxy b
connection c
proxyAddress Maybe d
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Proxy
proxy' <- a -> IO (Ptr Proxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
Ptr IOStream
connection' <- b -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
connection
Ptr ProxyAddress
proxyAddress' <- c -> IO (Ptr ProxyAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
proxyAddress
Ptr Cancellable
maybeCancellable <- case Maybe d
cancellable of
Maybe d
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just d
jCancellable -> do
Ptr Cancellable
jCancellable' <- d -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr d
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr Proxy
-> Ptr IOStream
-> Ptr ProxyAddress
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_proxy_connect_async Ptr Proxy
proxy' Ptr IOStream
connection' Ptr ProxyAddress
proxyAddress' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
connection
c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
proxyAddress
Maybe d -> (d -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe d
cancellable d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ProxyConnectAsyncMethodInfo
instance (signature ~ (b -> c -> Maybe (d) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsProxy a, Gio.IOStream.IsIOStream b, Gio.ProxyAddress.IsProxyAddress c, Gio.Cancellable.IsCancellable d) => O.MethodInfo ProxyConnectAsyncMethodInfo a signature where
overloadedMethod = proxyConnectAsync
#endif
foreign import ccall "g_proxy_connect_finish" g_proxy_connect_finish ::
Ptr Proxy ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr Gio.IOStream.IOStream)
proxyConnectFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsProxy a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m Gio.IOStream.IOStream
proxyConnectFinish :: a -> b -> m IOStream
proxyConnectFinish a
proxy b
result_ = IO IOStream -> m IOStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOStream -> m IOStream) -> IO IOStream -> m IOStream
forall a b. (a -> b) -> a -> b
$ do
Ptr Proxy
proxy' <- a -> IO (Ptr Proxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO IOStream -> IO () -> IO IOStream
forall a b. IO a -> IO b -> IO a
onException (do
Ptr IOStream
result <- (Ptr (Ptr GError) -> IO (Ptr IOStream)) -> IO (Ptr IOStream)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr IOStream)) -> IO (Ptr IOStream))
-> (Ptr (Ptr GError) -> IO (Ptr IOStream)) -> IO (Ptr IOStream)
forall a b. (a -> b) -> a -> b
$ Ptr Proxy
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr IOStream)
g_proxy_connect_finish Ptr Proxy
proxy' Ptr AsyncResult
result_'
Text -> Ptr IOStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyConnectFinish" Ptr IOStream
result
IOStream
result' <- ((ManagedPtr IOStream -> IOStream) -> Ptr IOStream -> IO IOStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr IOStream -> IOStream
Gio.IOStream.IOStream) Ptr IOStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
IOStream -> IO IOStream
forall (m :: * -> *) a. Monad m => a -> m a
return IOStream
result'
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data ProxyConnectFinishMethodInfo
instance (signature ~ (b -> m Gio.IOStream.IOStream), MonadIO m, IsProxy a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo ProxyConnectFinishMethodInfo a signature where
overloadedMethod = proxyConnectFinish
#endif
foreign import ccall "g_proxy_supports_hostname" g_proxy_supports_hostname ::
Ptr Proxy ->
IO CInt
proxySupportsHostname ::
(B.CallStack.HasCallStack, MonadIO m, IsProxy a) =>
a
-> m Bool
proxySupportsHostname :: a -> m Bool
proxySupportsHostname a
proxy = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Proxy
proxy' <- a -> IO (Ptr Proxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
CInt
result <- Ptr Proxy -> IO CInt
g_proxy_supports_hostname Ptr Proxy
proxy'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ProxySupportsHostnameMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsProxy a) => O.MethodInfo ProxySupportsHostnameMethodInfo a signature where
overloadedMethod = proxySupportsHostname
#endif
foreign import ccall "g_proxy_get_default_for_protocol" g_proxy_get_default_for_protocol ::
CString ->
IO (Ptr Proxy)
proxyGetDefaultForProtocol ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m Proxy
proxyGetDefaultForProtocol :: Text -> m Proxy
proxyGetDefaultForProtocol Text
protocol = IO Proxy -> m Proxy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Proxy -> m Proxy) -> IO Proxy -> m Proxy
forall a b. (a -> b) -> a -> b
$ do
CString
protocol' <- Text -> IO CString
textToCString Text
protocol
Ptr Proxy
result <- CString -> IO (Ptr Proxy)
g_proxy_get_default_for_protocol CString
protocol'
Text -> Ptr Proxy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"proxyGetDefaultForProtocol" Ptr Proxy
result
Proxy
result' <- ((ManagedPtr Proxy -> Proxy) -> Ptr Proxy -> IO Proxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Proxy -> Proxy
Proxy) Ptr Proxy
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
protocol'
Proxy -> IO Proxy
forall (m :: * -> *) a. Monad m => a -> m a
return Proxy
result'
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Proxy = ProxySignalList
type ProxySignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif