{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.SimpleProxyResolver
(
SimpleProxyResolver(..) ,
IsSimpleProxyResolver ,
toSimpleProxyResolver ,
noSimpleProxyResolver ,
#if defined(ENABLE_OVERLOADING)
ResolveSimpleProxyResolverMethod ,
#endif
simpleProxyResolverNew ,
#if defined(ENABLE_OVERLOADING)
SimpleProxyResolverSetDefaultProxyMethodInfo,
#endif
simpleProxyResolverSetDefaultProxy ,
#if defined(ENABLE_OVERLOADING)
SimpleProxyResolverSetIgnoreHostsMethodInfo,
#endif
simpleProxyResolverSetIgnoreHosts ,
#if defined(ENABLE_OVERLOADING)
SimpleProxyResolverSetUriProxyMethodInfo,
#endif
simpleProxyResolverSetUriProxy ,
#if defined(ENABLE_OVERLOADING)
SimpleProxyResolverDefaultProxyPropertyInfo,
#endif
constructSimpleProxyResolverDefaultProxy,
getSimpleProxyResolverDefaultProxy ,
setSimpleProxyResolverDefaultProxy ,
#if defined(ENABLE_OVERLOADING)
simpleProxyResolverDefaultProxy ,
#endif
#if defined(ENABLE_OVERLOADING)
SimpleProxyResolverIgnoreHostsPropertyInfo,
#endif
clearSimpleProxyResolverIgnoreHosts ,
constructSimpleProxyResolverIgnoreHosts ,
getSimpleProxyResolverIgnoreHosts ,
setSimpleProxyResolverIgnoreHosts ,
#if defined(ENABLE_OVERLOADING)
simpleProxyResolverIgnoreHosts ,
#endif
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.ProxyResolver as Gio.ProxyResolver
newtype SimpleProxyResolver = SimpleProxyResolver (ManagedPtr SimpleProxyResolver)
deriving (SimpleProxyResolver -> SimpleProxyResolver -> Bool
(SimpleProxyResolver -> SimpleProxyResolver -> Bool)
-> (SimpleProxyResolver -> SimpleProxyResolver -> Bool)
-> Eq SimpleProxyResolver
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleProxyResolver -> SimpleProxyResolver -> Bool
$c/= :: SimpleProxyResolver -> SimpleProxyResolver -> Bool
== :: SimpleProxyResolver -> SimpleProxyResolver -> Bool
$c== :: SimpleProxyResolver -> SimpleProxyResolver -> Bool
Eq)
foreign import ccall "g_simple_proxy_resolver_get_type"
c_g_simple_proxy_resolver_get_type :: IO GType
instance GObject SimpleProxyResolver where
gobjectType :: IO GType
gobjectType = IO GType
c_g_simple_proxy_resolver_get_type
instance B.GValue.IsGValue SimpleProxyResolver where
toGValue :: SimpleProxyResolver -> IO GValue
toGValue o :: SimpleProxyResolver
o = do
GType
gtype <- IO GType
c_g_simple_proxy_resolver_get_type
SimpleProxyResolver
-> (Ptr SimpleProxyResolver -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SimpleProxyResolver
o (GType
-> (GValue -> Ptr SimpleProxyResolver -> IO ())
-> Ptr SimpleProxyResolver
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SimpleProxyResolver -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO SimpleProxyResolver
fromGValue gv :: GValue
gv = do
Ptr SimpleProxyResolver
ptr <- GValue -> IO (Ptr SimpleProxyResolver)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr SimpleProxyResolver)
(ManagedPtr SimpleProxyResolver -> SimpleProxyResolver)
-> Ptr SimpleProxyResolver -> IO SimpleProxyResolver
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SimpleProxyResolver -> SimpleProxyResolver
SimpleProxyResolver Ptr SimpleProxyResolver
ptr
class (GObject o, O.IsDescendantOf SimpleProxyResolver o) => IsSimpleProxyResolver o
instance (GObject o, O.IsDescendantOf SimpleProxyResolver o) => IsSimpleProxyResolver o
instance O.HasParentTypes SimpleProxyResolver
type instance O.ParentTypes SimpleProxyResolver = '[GObject.Object.Object, Gio.ProxyResolver.ProxyResolver]
toSimpleProxyResolver :: (MonadIO m, IsSimpleProxyResolver o) => o -> m SimpleProxyResolver
toSimpleProxyResolver :: o -> m SimpleProxyResolver
toSimpleProxyResolver = IO SimpleProxyResolver -> m SimpleProxyResolver
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SimpleProxyResolver -> m SimpleProxyResolver)
-> (o -> IO SimpleProxyResolver) -> o -> m SimpleProxyResolver
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SimpleProxyResolver -> SimpleProxyResolver)
-> o -> IO SimpleProxyResolver
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr SimpleProxyResolver -> SimpleProxyResolver
SimpleProxyResolver
noSimpleProxyResolver :: Maybe SimpleProxyResolver
noSimpleProxyResolver :: Maybe SimpleProxyResolver
noSimpleProxyResolver = Maybe SimpleProxyResolver
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveSimpleProxyResolverMethod (t :: Symbol) (o :: *) :: * where
ResolveSimpleProxyResolverMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSimpleProxyResolverMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSimpleProxyResolverMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSimpleProxyResolverMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSimpleProxyResolverMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSimpleProxyResolverMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSimpleProxyResolverMethod "isSupported" o = Gio.ProxyResolver.ProxyResolverIsSupportedMethodInfo
ResolveSimpleProxyResolverMethod "lookup" o = Gio.ProxyResolver.ProxyResolverLookupMethodInfo
ResolveSimpleProxyResolverMethod "lookupAsync" o = Gio.ProxyResolver.ProxyResolverLookupAsyncMethodInfo
ResolveSimpleProxyResolverMethod "lookupFinish" o = Gio.ProxyResolver.ProxyResolverLookupFinishMethodInfo
ResolveSimpleProxyResolverMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSimpleProxyResolverMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSimpleProxyResolverMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSimpleProxyResolverMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSimpleProxyResolverMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSimpleProxyResolverMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSimpleProxyResolverMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSimpleProxyResolverMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSimpleProxyResolverMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSimpleProxyResolverMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSimpleProxyResolverMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSimpleProxyResolverMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSimpleProxyResolverMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSimpleProxyResolverMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSimpleProxyResolverMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSimpleProxyResolverMethod "setDefaultProxy" o = SimpleProxyResolverSetDefaultProxyMethodInfo
ResolveSimpleProxyResolverMethod "setIgnoreHosts" o = SimpleProxyResolverSetIgnoreHostsMethodInfo
ResolveSimpleProxyResolverMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSimpleProxyResolverMethod "setUriProxy" o = SimpleProxyResolverSetUriProxyMethodInfo
ResolveSimpleProxyResolverMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSimpleProxyResolverMethod t SimpleProxyResolver, O.MethodInfo info SimpleProxyResolver p) => OL.IsLabel t (SimpleProxyResolver -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getSimpleProxyResolverDefaultProxy :: (MonadIO m, IsSimpleProxyResolver o) => o -> m (Maybe T.Text)
getSimpleProxyResolverDefaultProxy :: o -> m (Maybe Text)
getSimpleProxyResolverDefaultProxy obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "default-proxy"
setSimpleProxyResolverDefaultProxy :: (MonadIO m, IsSimpleProxyResolver o) => o -> T.Text -> m ()
setSimpleProxyResolverDefaultProxy :: o -> Text -> m ()
setSimpleProxyResolverDefaultProxy obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "default-proxy" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructSimpleProxyResolverDefaultProxy :: (IsSimpleProxyResolver o) => T.Text -> IO (GValueConstruct o)
constructSimpleProxyResolverDefaultProxy :: Text -> IO (GValueConstruct o)
constructSimpleProxyResolverDefaultProxy val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "default-proxy" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
#if defined(ENABLE_OVERLOADING)
data SimpleProxyResolverDefaultProxyPropertyInfo
instance AttrInfo SimpleProxyResolverDefaultProxyPropertyInfo where
type AttrAllowedOps SimpleProxyResolverDefaultProxyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint SimpleProxyResolverDefaultProxyPropertyInfo = IsSimpleProxyResolver
type AttrSetTypeConstraint SimpleProxyResolverDefaultProxyPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint SimpleProxyResolverDefaultProxyPropertyInfo = (~) T.Text
type AttrTransferType SimpleProxyResolverDefaultProxyPropertyInfo = T.Text
type AttrGetType SimpleProxyResolverDefaultProxyPropertyInfo = (Maybe T.Text)
type AttrLabel SimpleProxyResolverDefaultProxyPropertyInfo = "default-proxy"
type AttrOrigin SimpleProxyResolverDefaultProxyPropertyInfo = SimpleProxyResolver
attrGet = getSimpleProxyResolverDefaultProxy
attrSet = setSimpleProxyResolverDefaultProxy
attrTransfer _ v = do
return v
attrConstruct = constructSimpleProxyResolverDefaultProxy
attrClear = undefined
#endif
getSimpleProxyResolverIgnoreHosts :: (MonadIO m, IsSimpleProxyResolver o) => o -> m (Maybe [T.Text])
getSimpleProxyResolverIgnoreHosts :: o -> m (Maybe [Text])
getSimpleProxyResolverIgnoreHosts obj :: o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj "ignore-hosts"
setSimpleProxyResolverIgnoreHosts :: (MonadIO m, IsSimpleProxyResolver o) => o -> [T.Text] -> m ()
setSimpleProxyResolverIgnoreHosts :: o -> [Text] -> m ()
setSimpleProxyResolverIgnoreHosts obj :: o
obj val :: [Text]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj "ignore-hosts" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructSimpleProxyResolverIgnoreHosts :: (IsSimpleProxyResolver o) => [T.Text] -> IO (GValueConstruct o)
constructSimpleProxyResolverIgnoreHosts :: [Text] -> IO (GValueConstruct o)
constructSimpleProxyResolverIgnoreHosts val :: [Text]
val = String -> Maybe [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray "ignore-hosts" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
clearSimpleProxyResolverIgnoreHosts :: (MonadIO m, IsSimpleProxyResolver o) => o -> m ()
clearSimpleProxyResolverIgnoreHosts :: o -> m ()
clearSimpleProxyResolverIgnoreHosts obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj "ignore-hosts" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data SimpleProxyResolverIgnoreHostsPropertyInfo
instance AttrInfo SimpleProxyResolverIgnoreHostsPropertyInfo where
type AttrAllowedOps SimpleProxyResolverIgnoreHostsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SimpleProxyResolverIgnoreHostsPropertyInfo = IsSimpleProxyResolver
type AttrSetTypeConstraint SimpleProxyResolverIgnoreHostsPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint SimpleProxyResolverIgnoreHostsPropertyInfo = (~) [T.Text]
type AttrTransferType SimpleProxyResolverIgnoreHostsPropertyInfo = [T.Text]
type AttrGetType SimpleProxyResolverIgnoreHostsPropertyInfo = (Maybe [T.Text])
type AttrLabel SimpleProxyResolverIgnoreHostsPropertyInfo = "ignore-hosts"
type AttrOrigin SimpleProxyResolverIgnoreHostsPropertyInfo = SimpleProxyResolver
attrGet = getSimpleProxyResolverIgnoreHosts
attrSet = setSimpleProxyResolverIgnoreHosts
attrTransfer _ v = do
return v
attrConstruct = constructSimpleProxyResolverIgnoreHosts
attrClear = clearSimpleProxyResolverIgnoreHosts
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SimpleProxyResolver
type instance O.AttributeList SimpleProxyResolver = SimpleProxyResolverAttributeList
type SimpleProxyResolverAttributeList = ('[ '("defaultProxy", SimpleProxyResolverDefaultProxyPropertyInfo), '("ignoreHosts", SimpleProxyResolverIgnoreHostsPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
simpleProxyResolverDefaultProxy :: AttrLabelProxy "defaultProxy"
simpleProxyResolverDefaultProxy = AttrLabelProxy
simpleProxyResolverIgnoreHosts :: AttrLabelProxy "ignoreHosts"
simpleProxyResolverIgnoreHosts = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SimpleProxyResolver = SimpleProxyResolverSignalList
type SimpleProxyResolverSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_simple_proxy_resolver_set_default_proxy" g_simple_proxy_resolver_set_default_proxy ::
Ptr SimpleProxyResolver ->
CString ->
IO ()
simpleProxyResolverSetDefaultProxy ::
(B.CallStack.HasCallStack, MonadIO m, IsSimpleProxyResolver a) =>
a
-> T.Text
-> m ()
simpleProxyResolverSetDefaultProxy :: a -> Text -> m ()
simpleProxyResolverSetDefaultProxy resolver :: a
resolver defaultProxy :: Text
defaultProxy = 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 SimpleProxyResolver
resolver' <- a -> IO (Ptr SimpleProxyResolver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
resolver
CString
defaultProxy' <- Text -> IO CString
textToCString Text
defaultProxy
Ptr SimpleProxyResolver -> CString -> IO ()
g_simple_proxy_resolver_set_default_proxy Ptr SimpleProxyResolver
resolver' CString
defaultProxy'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
resolver
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
defaultProxy'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SimpleProxyResolverSetDefaultProxyMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSimpleProxyResolver a) => O.MethodInfo SimpleProxyResolverSetDefaultProxyMethodInfo a signature where
overloadedMethod = simpleProxyResolverSetDefaultProxy
#endif
foreign import ccall "g_simple_proxy_resolver_set_ignore_hosts" g_simple_proxy_resolver_set_ignore_hosts ::
Ptr SimpleProxyResolver ->
CString ->
IO ()
simpleProxyResolverSetIgnoreHosts ::
(B.CallStack.HasCallStack, MonadIO m, IsSimpleProxyResolver a) =>
a
-> T.Text
-> m ()
simpleProxyResolverSetIgnoreHosts :: a -> Text -> m ()
simpleProxyResolverSetIgnoreHosts resolver :: a
resolver ignoreHosts :: Text
ignoreHosts = 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 SimpleProxyResolver
resolver' <- a -> IO (Ptr SimpleProxyResolver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
resolver
CString
ignoreHosts' <- Text -> IO CString
textToCString Text
ignoreHosts
Ptr SimpleProxyResolver -> CString -> IO ()
g_simple_proxy_resolver_set_ignore_hosts Ptr SimpleProxyResolver
resolver' CString
ignoreHosts'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
resolver
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
ignoreHosts'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SimpleProxyResolverSetIgnoreHostsMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSimpleProxyResolver a) => O.MethodInfo SimpleProxyResolverSetIgnoreHostsMethodInfo a signature where
overloadedMethod = simpleProxyResolverSetIgnoreHosts
#endif
foreign import ccall "g_simple_proxy_resolver_set_uri_proxy" g_simple_proxy_resolver_set_uri_proxy ::
Ptr SimpleProxyResolver ->
CString ->
CString ->
IO ()
simpleProxyResolverSetUriProxy ::
(B.CallStack.HasCallStack, MonadIO m, IsSimpleProxyResolver a) =>
a
-> T.Text
-> T.Text
-> m ()
simpleProxyResolverSetUriProxy :: a -> Text -> Text -> m ()
simpleProxyResolverSetUriProxy resolver :: a
resolver uriScheme :: Text
uriScheme proxy :: Text
proxy = 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 SimpleProxyResolver
resolver' <- a -> IO (Ptr SimpleProxyResolver)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
resolver
CString
uriScheme' <- Text -> IO CString
textToCString Text
uriScheme
CString
proxy' <- Text -> IO CString
textToCString Text
proxy
Ptr SimpleProxyResolver -> CString -> CString -> IO ()
g_simple_proxy_resolver_set_uri_proxy Ptr SimpleProxyResolver
resolver' CString
uriScheme' CString
proxy'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
resolver
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uriScheme'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
proxy'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SimpleProxyResolverSetUriProxyMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m, IsSimpleProxyResolver a) => O.MethodInfo SimpleProxyResolverSetUriProxyMethodInfo a signature where
overloadedMethod = simpleProxyResolverSetUriProxy
#endif
foreign import ccall "g_simple_proxy_resolver_new" g_simple_proxy_resolver_new ::
CString ->
CString ->
IO (Ptr Gio.ProxyResolver.ProxyResolver)
simpleProxyResolverNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe (T.Text)
-> Maybe (T.Text)
-> m Gio.ProxyResolver.ProxyResolver
simpleProxyResolverNew :: Maybe Text -> Maybe Text -> m ProxyResolver
simpleProxyResolverNew defaultProxy :: Maybe Text
defaultProxy ignoreHosts :: Maybe Text
ignoreHosts = IO ProxyResolver -> m ProxyResolver
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ProxyResolver -> m ProxyResolver)
-> IO ProxyResolver -> m ProxyResolver
forall a b. (a -> b) -> a -> b
$ do
CString
maybeDefaultProxy <- case Maybe Text
defaultProxy of
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jDefaultProxy :: Text
jDefaultProxy -> do
CString
jDefaultProxy' <- Text -> IO CString
textToCString Text
jDefaultProxy
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jDefaultProxy'
CString
maybeIgnoreHosts <- case Maybe Text
ignoreHosts of
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jIgnoreHosts :: Text
jIgnoreHosts -> do
CString
jIgnoreHosts' <- Text -> IO CString
textToCString Text
jIgnoreHosts
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jIgnoreHosts'
Ptr ProxyResolver
result <- CString -> CString -> IO (Ptr ProxyResolver)
g_simple_proxy_resolver_new CString
maybeDefaultProxy CString
maybeIgnoreHosts
Text -> Ptr ProxyResolver -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "simpleProxyResolverNew" Ptr ProxyResolver
result
ProxyResolver
result' <- ((ManagedPtr ProxyResolver -> ProxyResolver)
-> Ptr ProxyResolver -> IO ProxyResolver
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ProxyResolver -> ProxyResolver
Gio.ProxyResolver.ProxyResolver) Ptr ProxyResolver
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeDefaultProxy
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeIgnoreHosts
ProxyResolver -> IO ProxyResolver
forall (m :: * -> *) a. Monad m => a -> m a
return ProxyResolver
result'
#if defined(ENABLE_OVERLOADING)
#endif