module GI.Soup.Objects.Session
(
Session(..) ,
SessionK ,
toSession ,
noSession ,
sessionAbort ,
sessionAddFeature ,
sessionAddFeatureByType ,
sessionCancelMessage ,
sessionGetAsyncContext ,
sessionGetFeature ,
sessionGetFeatureForMessage ,
sessionGetFeatures ,
sessionHasFeature ,
sessionNew ,
sessionPauseMessage ,
sessionPrefetchDns ,
sessionPrepareForUri ,
sessionQueueMessage ,
sessionRedirectMessage ,
sessionRemoveFeature ,
sessionRemoveFeatureByType ,
sessionRequest ,
sessionRequestHttp ,
sessionRequestHttpUri ,
sessionRequestUri ,
sessionRequeueMessage ,
sessionSend ,
sessionSendAsync ,
sessionSendFinish ,
sessionSendMessage ,
sessionStealConnection ,
sessionUnpauseMessage ,
sessionWebsocketConnectAsync ,
sessionWebsocketConnectFinish ,
sessionWouldRedirect ,
SessionAcceptLanguagePropertyInfo ,
constructSessionAcceptLanguage ,
getSessionAcceptLanguage ,
setSessionAcceptLanguage ,
SessionAcceptLanguageAutoPropertyInfo ,
constructSessionAcceptLanguageAuto ,
getSessionAcceptLanguageAuto ,
setSessionAcceptLanguageAuto ,
SessionAsyncContextPropertyInfo ,
constructSessionAsyncContext ,
getSessionAsyncContext ,
SessionHttpAliasesPropertyInfo ,
constructSessionHttpAliases ,
getSessionHttpAliases ,
setSessionHttpAliases ,
SessionHttpsAliasesPropertyInfo ,
constructSessionHttpsAliases ,
getSessionHttpsAliases ,
setSessionHttpsAliases ,
SessionIdleTimeoutPropertyInfo ,
constructSessionIdleTimeout ,
getSessionIdleTimeout ,
setSessionIdleTimeout ,
SessionLocalAddressPropertyInfo ,
constructSessionLocalAddress ,
getSessionLocalAddress ,
SessionMaxConnsPropertyInfo ,
constructSessionMaxConns ,
getSessionMaxConns ,
setSessionMaxConns ,
SessionMaxConnsPerHostPropertyInfo ,
constructSessionMaxConnsPerHost ,
getSessionMaxConnsPerHost ,
setSessionMaxConnsPerHost ,
SessionProxyResolverPropertyInfo ,
constructSessionProxyResolver ,
getSessionProxyResolver ,
setSessionProxyResolver ,
SessionProxyUriPropertyInfo ,
constructSessionProxyUri ,
getSessionProxyUri ,
setSessionProxyUri ,
SessionSslCaFilePropertyInfo ,
constructSessionSslCaFile ,
getSessionSslCaFile ,
setSessionSslCaFile ,
SessionSslStrictPropertyInfo ,
constructSessionSslStrict ,
getSessionSslStrict ,
setSessionSslStrict ,
SessionSslUseSystemCaFilePropertyInfo ,
constructSessionSslUseSystemCaFile ,
getSessionSslUseSystemCaFile ,
setSessionSslUseSystemCaFile ,
SessionTimeoutPropertyInfo ,
constructSessionTimeout ,
getSessionTimeout ,
setSessionTimeout ,
SessionTlsDatabasePropertyInfo ,
constructSessionTlsDatabase ,
getSessionTlsDatabase ,
setSessionTlsDatabase ,
SessionTlsInteractionPropertyInfo ,
constructSessionTlsInteraction ,
getSessionTlsInteraction ,
setSessionTlsInteraction ,
SessionUseNtlmPropertyInfo ,
constructSessionUseNtlm ,
getSessionUseNtlm ,
setSessionUseNtlm ,
SessionUseThreadContextPropertyInfo ,
constructSessionUseThreadContext ,
getSessionUseThreadContext ,
setSessionUseThreadContext ,
SessionUserAgentPropertyInfo ,
constructSessionUserAgent ,
getSessionUserAgent ,
setSessionUserAgent ,
SessionAuthenticateCallback ,
SessionAuthenticateCallbackC ,
SessionAuthenticateSignalInfo ,
afterSessionAuthenticate ,
mkSessionAuthenticateCallback ,
noSessionAuthenticateCallback ,
onSessionAuthenticate ,
sessionAuthenticateCallbackWrapper ,
sessionAuthenticateClosure ,
SessionConnectionCreatedCallback ,
SessionConnectionCreatedCallbackC ,
SessionConnectionCreatedSignalInfo ,
afterSessionConnectionCreated ,
mkSessionConnectionCreatedCallback ,
noSessionConnectionCreatedCallback ,
onSessionConnectionCreated ,
sessionConnectionCreatedCallbackWrapper ,
sessionConnectionCreatedClosure ,
SessionRequestQueuedCallback ,
SessionRequestQueuedCallbackC ,
SessionRequestQueuedSignalInfo ,
afterSessionRequestQueued ,
mkSessionRequestQueuedCallback ,
noSessionRequestQueuedCallback ,
onSessionRequestQueued ,
sessionRequestQueuedCallbackWrapper ,
sessionRequestQueuedClosure ,
SessionRequestStartedCallback ,
SessionRequestStartedCallbackC ,
SessionRequestStartedSignalInfo ,
afterSessionRequestStarted ,
mkSessionRequestStartedCallback ,
noSessionRequestStartedCallback ,
onSessionRequestStarted ,
sessionRequestStartedCallbackWrapper ,
sessionRequestStartedClosure ,
SessionRequestUnqueuedCallback ,
SessionRequestUnqueuedCallbackC ,
SessionRequestUnqueuedSignalInfo ,
afterSessionRequestUnqueued ,
mkSessionRequestUnqueuedCallback ,
noSessionRequestUnqueuedCallback ,
onSessionRequestUnqueued ,
sessionRequestUnqueuedCallbackWrapper ,
sessionRequestUnqueuedClosure ,
SessionTunnelingCallback ,
SessionTunnelingCallbackC ,
SessionTunnelingSignalInfo ,
afterSessionTunneling ,
mkSessionTunnelingCallback ,
noSessionTunnelingCallback ,
onSessionTunneling ,
sessionTunnelingCallbackWrapper ,
sessionTunnelingClosure ,
) where
import Prelude ()
import Data.GI.Base.ShortPrelude
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import GI.Soup.Types
import GI.Soup.Callbacks
import qualified GI.GLib as GLib
import qualified GI.GObject as GObject
import qualified GI.Gio as Gio
newtype Session = Session (ForeignPtr Session)
foreign import ccall "soup_session_get_type"
c_soup_session_get_type :: IO GType
type instance ParentTypes Session = SessionParentTypes
type SessionParentTypes = '[GObject.Object]
instance GObject Session where
gobjectIsInitiallyUnowned _ = False
gobjectType _ = c_soup_session_get_type
class GObject o => SessionK o
instance (GObject o, IsDescendantOf Session o) => SessionK o
toSession :: SessionK o => o -> IO Session
toSession = unsafeCastTo Session
noSession :: Maybe Session
noSession = Nothing
type SessionAuthenticateCallback =
Message ->
Auth ->
Bool ->
IO ()
noSessionAuthenticateCallback :: Maybe SessionAuthenticateCallback
noSessionAuthenticateCallback = Nothing
type SessionAuthenticateCallbackC =
Ptr () ->
Ptr Message ->
Ptr Auth ->
CInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mkSessionAuthenticateCallback :: SessionAuthenticateCallbackC -> IO (FunPtr SessionAuthenticateCallbackC)
sessionAuthenticateClosure :: SessionAuthenticateCallback -> IO Closure
sessionAuthenticateClosure cb = newCClosure =<< mkSessionAuthenticateCallback wrapped
where wrapped = sessionAuthenticateCallbackWrapper cb
sessionAuthenticateCallbackWrapper ::
SessionAuthenticateCallback ->
Ptr () ->
Ptr Message ->
Ptr Auth ->
CInt ->
Ptr () ->
IO ()
sessionAuthenticateCallbackWrapper _cb _ msg auth retrying _ = do
msg' <- (newObject Message) msg
auth' <- (newObject Auth) auth
let retrying' = (/= 0) retrying
_cb msg' auth' retrying'
onSessionAuthenticate :: (GObject a, MonadIO m) => a -> SessionAuthenticateCallback -> m SignalHandlerId
onSessionAuthenticate obj cb = liftIO $ connectSessionAuthenticate obj cb SignalConnectBefore
afterSessionAuthenticate :: (GObject a, MonadIO m) => a -> SessionAuthenticateCallback -> m SignalHandlerId
afterSessionAuthenticate obj cb = connectSessionAuthenticate obj cb SignalConnectAfter
connectSessionAuthenticate :: (GObject a, MonadIO m) =>
a -> SessionAuthenticateCallback -> SignalConnectMode -> m SignalHandlerId
connectSessionAuthenticate obj cb after = liftIO $ do
cb' <- mkSessionAuthenticateCallback (sessionAuthenticateCallbackWrapper cb)
connectSignalFunPtr obj "authenticate" cb' after
type SessionConnectionCreatedCallback =
GObject.Object ->
IO ()
noSessionConnectionCreatedCallback :: Maybe SessionConnectionCreatedCallback
noSessionConnectionCreatedCallback = Nothing
type SessionConnectionCreatedCallbackC =
Ptr () ->
Ptr GObject.Object ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mkSessionConnectionCreatedCallback :: SessionConnectionCreatedCallbackC -> IO (FunPtr SessionConnectionCreatedCallbackC)
sessionConnectionCreatedClosure :: SessionConnectionCreatedCallback -> IO Closure
sessionConnectionCreatedClosure cb = newCClosure =<< mkSessionConnectionCreatedCallback wrapped
where wrapped = sessionConnectionCreatedCallbackWrapper cb
sessionConnectionCreatedCallbackWrapper ::
SessionConnectionCreatedCallback ->
Ptr () ->
Ptr GObject.Object ->
Ptr () ->
IO ()
sessionConnectionCreatedCallbackWrapper _cb _ connection _ = do
connection' <- (newObject GObject.Object) connection
_cb connection'
onSessionConnectionCreated :: (GObject a, MonadIO m) => a -> SessionConnectionCreatedCallback -> m SignalHandlerId
onSessionConnectionCreated obj cb = liftIO $ connectSessionConnectionCreated obj cb SignalConnectBefore
afterSessionConnectionCreated :: (GObject a, MonadIO m) => a -> SessionConnectionCreatedCallback -> m SignalHandlerId
afterSessionConnectionCreated obj cb = connectSessionConnectionCreated obj cb SignalConnectAfter
connectSessionConnectionCreated :: (GObject a, MonadIO m) =>
a -> SessionConnectionCreatedCallback -> SignalConnectMode -> m SignalHandlerId
connectSessionConnectionCreated obj cb after = liftIO $ do
cb' <- mkSessionConnectionCreatedCallback (sessionConnectionCreatedCallbackWrapper cb)
connectSignalFunPtr obj "connection-created" cb' after
type SessionRequestQueuedCallback =
Message ->
IO ()
noSessionRequestQueuedCallback :: Maybe SessionRequestQueuedCallback
noSessionRequestQueuedCallback = Nothing
type SessionRequestQueuedCallbackC =
Ptr () ->
Ptr Message ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mkSessionRequestQueuedCallback :: SessionRequestQueuedCallbackC -> IO (FunPtr SessionRequestQueuedCallbackC)
sessionRequestQueuedClosure :: SessionRequestQueuedCallback -> IO Closure
sessionRequestQueuedClosure cb = newCClosure =<< mkSessionRequestQueuedCallback wrapped
where wrapped = sessionRequestQueuedCallbackWrapper cb
sessionRequestQueuedCallbackWrapper ::
SessionRequestQueuedCallback ->
Ptr () ->
Ptr Message ->
Ptr () ->
IO ()
sessionRequestQueuedCallbackWrapper _cb _ msg _ = do
msg' <- (newObject Message) msg
_cb msg'
onSessionRequestQueued :: (GObject a, MonadIO m) => a -> SessionRequestQueuedCallback -> m SignalHandlerId
onSessionRequestQueued obj cb = liftIO $ connectSessionRequestQueued obj cb SignalConnectBefore
afterSessionRequestQueued :: (GObject a, MonadIO m) => a -> SessionRequestQueuedCallback -> m SignalHandlerId
afterSessionRequestQueued obj cb = connectSessionRequestQueued obj cb SignalConnectAfter
connectSessionRequestQueued :: (GObject a, MonadIO m) =>
a -> SessionRequestQueuedCallback -> SignalConnectMode -> m SignalHandlerId
connectSessionRequestQueued obj cb after = liftIO $ do
cb' <- mkSessionRequestQueuedCallback (sessionRequestQueuedCallbackWrapper cb)
connectSignalFunPtr obj "request-queued" cb' after
type SessionRequestStartedCallback =
Message ->
Socket ->
IO ()
noSessionRequestStartedCallback :: Maybe SessionRequestStartedCallback
noSessionRequestStartedCallback = Nothing
type SessionRequestStartedCallbackC =
Ptr () ->
Ptr Message ->
Ptr Socket ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mkSessionRequestStartedCallback :: SessionRequestStartedCallbackC -> IO (FunPtr SessionRequestStartedCallbackC)
sessionRequestStartedClosure :: SessionRequestStartedCallback -> IO Closure
sessionRequestStartedClosure cb = newCClosure =<< mkSessionRequestStartedCallback wrapped
where wrapped = sessionRequestStartedCallbackWrapper cb
sessionRequestStartedCallbackWrapper ::
SessionRequestStartedCallback ->
Ptr () ->
Ptr Message ->
Ptr Socket ->
Ptr () ->
IO ()
sessionRequestStartedCallbackWrapper _cb _ msg socket _ = do
msg' <- (newObject Message) msg
socket' <- (newObject Socket) socket
_cb msg' socket'
onSessionRequestStarted :: (GObject a, MonadIO m) => a -> SessionRequestStartedCallback -> m SignalHandlerId
onSessionRequestStarted obj cb = liftIO $ connectSessionRequestStarted obj cb SignalConnectBefore
afterSessionRequestStarted :: (GObject a, MonadIO m) => a -> SessionRequestStartedCallback -> m SignalHandlerId
afterSessionRequestStarted obj cb = connectSessionRequestStarted obj cb SignalConnectAfter
connectSessionRequestStarted :: (GObject a, MonadIO m) =>
a -> SessionRequestStartedCallback -> SignalConnectMode -> m SignalHandlerId
connectSessionRequestStarted obj cb after = liftIO $ do
cb' <- mkSessionRequestStartedCallback (sessionRequestStartedCallbackWrapper cb)
connectSignalFunPtr obj "request-started" cb' after
type SessionRequestUnqueuedCallback =
Message ->
IO ()
noSessionRequestUnqueuedCallback :: Maybe SessionRequestUnqueuedCallback
noSessionRequestUnqueuedCallback = Nothing
type SessionRequestUnqueuedCallbackC =
Ptr () ->
Ptr Message ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mkSessionRequestUnqueuedCallback :: SessionRequestUnqueuedCallbackC -> IO (FunPtr SessionRequestUnqueuedCallbackC)
sessionRequestUnqueuedClosure :: SessionRequestUnqueuedCallback -> IO Closure
sessionRequestUnqueuedClosure cb = newCClosure =<< mkSessionRequestUnqueuedCallback wrapped
where wrapped = sessionRequestUnqueuedCallbackWrapper cb
sessionRequestUnqueuedCallbackWrapper ::
SessionRequestUnqueuedCallback ->
Ptr () ->
Ptr Message ->
Ptr () ->
IO ()
sessionRequestUnqueuedCallbackWrapper _cb _ msg _ = do
msg' <- (newObject Message) msg
_cb msg'
onSessionRequestUnqueued :: (GObject a, MonadIO m) => a -> SessionRequestUnqueuedCallback -> m SignalHandlerId
onSessionRequestUnqueued obj cb = liftIO $ connectSessionRequestUnqueued obj cb SignalConnectBefore
afterSessionRequestUnqueued :: (GObject a, MonadIO m) => a -> SessionRequestUnqueuedCallback -> m SignalHandlerId
afterSessionRequestUnqueued obj cb = connectSessionRequestUnqueued obj cb SignalConnectAfter
connectSessionRequestUnqueued :: (GObject a, MonadIO m) =>
a -> SessionRequestUnqueuedCallback -> SignalConnectMode -> m SignalHandlerId
connectSessionRequestUnqueued obj cb after = liftIO $ do
cb' <- mkSessionRequestUnqueuedCallback (sessionRequestUnqueuedCallbackWrapper cb)
connectSignalFunPtr obj "request-unqueued" cb' after
type SessionTunnelingCallback =
GObject.Object ->
IO ()
noSessionTunnelingCallback :: Maybe SessionTunnelingCallback
noSessionTunnelingCallback = Nothing
type SessionTunnelingCallbackC =
Ptr () ->
Ptr GObject.Object ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mkSessionTunnelingCallback :: SessionTunnelingCallbackC -> IO (FunPtr SessionTunnelingCallbackC)
sessionTunnelingClosure :: SessionTunnelingCallback -> IO Closure
sessionTunnelingClosure cb = newCClosure =<< mkSessionTunnelingCallback wrapped
where wrapped = sessionTunnelingCallbackWrapper cb
sessionTunnelingCallbackWrapper ::
SessionTunnelingCallback ->
Ptr () ->
Ptr GObject.Object ->
Ptr () ->
IO ()
sessionTunnelingCallbackWrapper _cb _ connection _ = do
connection' <- (newObject GObject.Object) connection
_cb connection'
onSessionTunneling :: (GObject a, MonadIO m) => a -> SessionTunnelingCallback -> m SignalHandlerId
onSessionTunneling obj cb = liftIO $ connectSessionTunneling obj cb SignalConnectBefore
afterSessionTunneling :: (GObject a, MonadIO m) => a -> SessionTunnelingCallback -> m SignalHandlerId
afterSessionTunneling obj cb = connectSessionTunneling obj cb SignalConnectAfter
connectSessionTunneling :: (GObject a, MonadIO m) =>
a -> SessionTunnelingCallback -> SignalConnectMode -> m SignalHandlerId
connectSessionTunneling obj cb after = liftIO $ do
cb' <- mkSessionTunnelingCallback (sessionTunnelingCallbackWrapper cb)
connectSignalFunPtr obj "tunneling" cb' after
getSessionAcceptLanguage :: (MonadIO m, SessionK o) => o -> m T.Text
getSessionAcceptLanguage obj = liftIO $ getObjectPropertyString obj "accept-language"
setSessionAcceptLanguage :: (MonadIO m, SessionK o) => o -> T.Text -> m ()
setSessionAcceptLanguage obj val = liftIO $ setObjectPropertyString obj "accept-language" val
constructSessionAcceptLanguage :: T.Text -> IO ([Char], GValue)
constructSessionAcceptLanguage val = constructObjectPropertyString "accept-language" val
data SessionAcceptLanguagePropertyInfo
instance AttrInfo SessionAcceptLanguagePropertyInfo where
type AttrAllowedOps SessionAcceptLanguagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionAcceptLanguagePropertyInfo = (~) T.Text
type AttrBaseTypeConstraint SessionAcceptLanguagePropertyInfo = SessionK
type AttrGetType SessionAcceptLanguagePropertyInfo = T.Text
type AttrLabel SessionAcceptLanguagePropertyInfo = "Session::accept-language"
attrGet _ = getSessionAcceptLanguage
attrSet _ = setSessionAcceptLanguage
attrConstruct _ = constructSessionAcceptLanguage
getSessionAcceptLanguageAuto :: (MonadIO m, SessionK o) => o -> m Bool
getSessionAcceptLanguageAuto obj = liftIO $ getObjectPropertyBool obj "accept-language-auto"
setSessionAcceptLanguageAuto :: (MonadIO m, SessionK o) => o -> Bool -> m ()
setSessionAcceptLanguageAuto obj val = liftIO $ setObjectPropertyBool obj "accept-language-auto" val
constructSessionAcceptLanguageAuto :: Bool -> IO ([Char], GValue)
constructSessionAcceptLanguageAuto val = constructObjectPropertyBool "accept-language-auto" val
data SessionAcceptLanguageAutoPropertyInfo
instance AttrInfo SessionAcceptLanguageAutoPropertyInfo where
type AttrAllowedOps SessionAcceptLanguageAutoPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionAcceptLanguageAutoPropertyInfo = (~) Bool
type AttrBaseTypeConstraint SessionAcceptLanguageAutoPropertyInfo = SessionK
type AttrGetType SessionAcceptLanguageAutoPropertyInfo = Bool
type AttrLabel SessionAcceptLanguageAutoPropertyInfo = "Session::accept-language-auto"
attrGet _ = getSessionAcceptLanguageAuto
attrSet _ = setSessionAcceptLanguageAuto
attrConstruct _ = constructSessionAcceptLanguageAuto
getSessionAsyncContext :: (MonadIO m, SessionK o) => o -> m (Ptr ())
getSessionAsyncContext obj = liftIO $ getObjectPropertyPtr obj "async-context"
constructSessionAsyncContext :: (Ptr ()) -> IO ([Char], GValue)
constructSessionAsyncContext val = constructObjectPropertyPtr "async-context" val
data SessionAsyncContextPropertyInfo
instance AttrInfo SessionAsyncContextPropertyInfo where
type AttrAllowedOps SessionAsyncContextPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionAsyncContextPropertyInfo = (~) (Ptr ())
type AttrBaseTypeConstraint SessionAsyncContextPropertyInfo = SessionK
type AttrGetType SessionAsyncContextPropertyInfo = (Ptr ())
type AttrLabel SessionAsyncContextPropertyInfo = "Session::async-context"
attrGet _ = getSessionAsyncContext
attrSet _ = undefined
attrConstruct _ = constructSessionAsyncContext
getSessionHttpAliases :: (MonadIO m, SessionK o) => o -> m [T.Text]
getSessionHttpAliases obj = liftIO $ getObjectPropertyStringArray obj "http-aliases"
setSessionHttpAliases :: (MonadIO m, SessionK o) => o -> [T.Text] -> m ()
setSessionHttpAliases obj val = liftIO $ setObjectPropertyStringArray obj "http-aliases" val
constructSessionHttpAliases :: [T.Text] -> IO ([Char], GValue)
constructSessionHttpAliases val = constructObjectPropertyStringArray "http-aliases" val
data SessionHttpAliasesPropertyInfo
instance AttrInfo SessionHttpAliasesPropertyInfo where
type AttrAllowedOps SessionHttpAliasesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionHttpAliasesPropertyInfo = (~) [T.Text]
type AttrBaseTypeConstraint SessionHttpAliasesPropertyInfo = SessionK
type AttrGetType SessionHttpAliasesPropertyInfo = [T.Text]
type AttrLabel SessionHttpAliasesPropertyInfo = "Session::http-aliases"
attrGet _ = getSessionHttpAliases
attrSet _ = setSessionHttpAliases
attrConstruct _ = constructSessionHttpAliases
getSessionHttpsAliases :: (MonadIO m, SessionK o) => o -> m [T.Text]
getSessionHttpsAliases obj = liftIO $ getObjectPropertyStringArray obj "https-aliases"
setSessionHttpsAliases :: (MonadIO m, SessionK o) => o -> [T.Text] -> m ()
setSessionHttpsAliases obj val = liftIO $ setObjectPropertyStringArray obj "https-aliases" val
constructSessionHttpsAliases :: [T.Text] -> IO ([Char], GValue)
constructSessionHttpsAliases val = constructObjectPropertyStringArray "https-aliases" val
data SessionHttpsAliasesPropertyInfo
instance AttrInfo SessionHttpsAliasesPropertyInfo where
type AttrAllowedOps SessionHttpsAliasesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionHttpsAliasesPropertyInfo = (~) [T.Text]
type AttrBaseTypeConstraint SessionHttpsAliasesPropertyInfo = SessionK
type AttrGetType SessionHttpsAliasesPropertyInfo = [T.Text]
type AttrLabel SessionHttpsAliasesPropertyInfo = "Session::https-aliases"
attrGet _ = getSessionHttpsAliases
attrSet _ = setSessionHttpsAliases
attrConstruct _ = constructSessionHttpsAliases
getSessionIdleTimeout :: (MonadIO m, SessionK o) => o -> m Word32
getSessionIdleTimeout obj = liftIO $ getObjectPropertyCUInt obj "idle-timeout"
setSessionIdleTimeout :: (MonadIO m, SessionK o) => o -> Word32 -> m ()
setSessionIdleTimeout obj val = liftIO $ setObjectPropertyCUInt obj "idle-timeout" val
constructSessionIdleTimeout :: Word32 -> IO ([Char], GValue)
constructSessionIdleTimeout val = constructObjectPropertyCUInt "idle-timeout" val
data SessionIdleTimeoutPropertyInfo
instance AttrInfo SessionIdleTimeoutPropertyInfo where
type AttrAllowedOps SessionIdleTimeoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionIdleTimeoutPropertyInfo = (~) Word32
type AttrBaseTypeConstraint SessionIdleTimeoutPropertyInfo = SessionK
type AttrGetType SessionIdleTimeoutPropertyInfo = Word32
type AttrLabel SessionIdleTimeoutPropertyInfo = "Session::idle-timeout"
attrGet _ = getSessionIdleTimeout
attrSet _ = setSessionIdleTimeout
attrConstruct _ = constructSessionIdleTimeout
getSessionLocalAddress :: (MonadIO m, SessionK o) => o -> m Address
getSessionLocalAddress obj = liftIO $ getObjectPropertyObject obj "local-address" Address
constructSessionLocalAddress :: (AddressK a) => a -> IO ([Char], GValue)
constructSessionLocalAddress val = constructObjectPropertyObject "local-address" val
data SessionLocalAddressPropertyInfo
instance AttrInfo SessionLocalAddressPropertyInfo where
type AttrAllowedOps SessionLocalAddressPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionLocalAddressPropertyInfo = AddressK
type AttrBaseTypeConstraint SessionLocalAddressPropertyInfo = SessionK
type AttrGetType SessionLocalAddressPropertyInfo = Address
type AttrLabel SessionLocalAddressPropertyInfo = "Session::local-address"
attrGet _ = getSessionLocalAddress
attrSet _ = undefined
attrConstruct _ = constructSessionLocalAddress
getSessionMaxConns :: (MonadIO m, SessionK o) => o -> m Int32
getSessionMaxConns obj = liftIO $ getObjectPropertyCInt obj "max-conns"
setSessionMaxConns :: (MonadIO m, SessionK o) => o -> Int32 -> m ()
setSessionMaxConns obj val = liftIO $ setObjectPropertyCInt obj "max-conns" val
constructSessionMaxConns :: Int32 -> IO ([Char], GValue)
constructSessionMaxConns val = constructObjectPropertyCInt "max-conns" val
data SessionMaxConnsPropertyInfo
instance AttrInfo SessionMaxConnsPropertyInfo where
type AttrAllowedOps SessionMaxConnsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionMaxConnsPropertyInfo = (~) Int32
type AttrBaseTypeConstraint SessionMaxConnsPropertyInfo = SessionK
type AttrGetType SessionMaxConnsPropertyInfo = Int32
type AttrLabel SessionMaxConnsPropertyInfo = "Session::max-conns"
attrGet _ = getSessionMaxConns
attrSet _ = setSessionMaxConns
attrConstruct _ = constructSessionMaxConns
getSessionMaxConnsPerHost :: (MonadIO m, SessionK o) => o -> m Int32
getSessionMaxConnsPerHost obj = liftIO $ getObjectPropertyCInt obj "max-conns-per-host"
setSessionMaxConnsPerHost :: (MonadIO m, SessionK o) => o -> Int32 -> m ()
setSessionMaxConnsPerHost obj val = liftIO $ setObjectPropertyCInt obj "max-conns-per-host" val
constructSessionMaxConnsPerHost :: Int32 -> IO ([Char], GValue)
constructSessionMaxConnsPerHost val = constructObjectPropertyCInt "max-conns-per-host" val
data SessionMaxConnsPerHostPropertyInfo
instance AttrInfo SessionMaxConnsPerHostPropertyInfo where
type AttrAllowedOps SessionMaxConnsPerHostPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionMaxConnsPerHostPropertyInfo = (~) Int32
type AttrBaseTypeConstraint SessionMaxConnsPerHostPropertyInfo = SessionK
type AttrGetType SessionMaxConnsPerHostPropertyInfo = Int32
type AttrLabel SessionMaxConnsPerHostPropertyInfo = "Session::max-conns-per-host"
attrGet _ = getSessionMaxConnsPerHost
attrSet _ = setSessionMaxConnsPerHost
attrConstruct _ = constructSessionMaxConnsPerHost
getSessionProxyResolver :: (MonadIO m, SessionK o) => o -> m Gio.ProxyResolver
getSessionProxyResolver obj = liftIO $ getObjectPropertyObject obj "proxy-resolver" Gio.ProxyResolver
setSessionProxyResolver :: (MonadIO m, SessionK o, Gio.ProxyResolverK a) => o -> a -> m ()
setSessionProxyResolver obj val = liftIO $ setObjectPropertyObject obj "proxy-resolver" val
constructSessionProxyResolver :: (Gio.ProxyResolverK a) => a -> IO ([Char], GValue)
constructSessionProxyResolver val = constructObjectPropertyObject "proxy-resolver" val
data SessionProxyResolverPropertyInfo
instance AttrInfo SessionProxyResolverPropertyInfo where
type AttrAllowedOps SessionProxyResolverPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionProxyResolverPropertyInfo = Gio.ProxyResolverK
type AttrBaseTypeConstraint SessionProxyResolverPropertyInfo = SessionK
type AttrGetType SessionProxyResolverPropertyInfo = Gio.ProxyResolver
type AttrLabel SessionProxyResolverPropertyInfo = "Session::proxy-resolver"
attrGet _ = getSessionProxyResolver
attrSet _ = setSessionProxyResolver
attrConstruct _ = constructSessionProxyResolver
getSessionProxyUri :: (MonadIO m, SessionK o) => o -> m URI
getSessionProxyUri obj = liftIO $ getObjectPropertyBoxed obj "proxy-uri" URI
setSessionProxyUri :: (MonadIO m, SessionK o) => o -> URI -> m ()
setSessionProxyUri obj val = liftIO $ setObjectPropertyBoxed obj "proxy-uri" val
constructSessionProxyUri :: URI -> IO ([Char], GValue)
constructSessionProxyUri val = constructObjectPropertyBoxed "proxy-uri" val
data SessionProxyUriPropertyInfo
instance AttrInfo SessionProxyUriPropertyInfo where
type AttrAllowedOps SessionProxyUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionProxyUriPropertyInfo = (~) URI
type AttrBaseTypeConstraint SessionProxyUriPropertyInfo = SessionK
type AttrGetType SessionProxyUriPropertyInfo = URI
type AttrLabel SessionProxyUriPropertyInfo = "Session::proxy-uri"
attrGet _ = getSessionProxyUri
attrSet _ = setSessionProxyUri
attrConstruct _ = constructSessionProxyUri
getSessionSslCaFile :: (MonadIO m, SessionK o) => o -> m T.Text
getSessionSslCaFile obj = liftIO $ getObjectPropertyString obj "ssl-ca-file"
setSessionSslCaFile :: (MonadIO m, SessionK o) => o -> T.Text -> m ()
setSessionSslCaFile obj val = liftIO $ setObjectPropertyString obj "ssl-ca-file" val
constructSessionSslCaFile :: T.Text -> IO ([Char], GValue)
constructSessionSslCaFile val = constructObjectPropertyString "ssl-ca-file" val
data SessionSslCaFilePropertyInfo
instance AttrInfo SessionSslCaFilePropertyInfo where
type AttrAllowedOps SessionSslCaFilePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionSslCaFilePropertyInfo = (~) T.Text
type AttrBaseTypeConstraint SessionSslCaFilePropertyInfo = SessionK
type AttrGetType SessionSslCaFilePropertyInfo = T.Text
type AttrLabel SessionSslCaFilePropertyInfo = "Session::ssl-ca-file"
attrGet _ = getSessionSslCaFile
attrSet _ = setSessionSslCaFile
attrConstruct _ = constructSessionSslCaFile
getSessionSslStrict :: (MonadIO m, SessionK o) => o -> m Bool
getSessionSslStrict obj = liftIO $ getObjectPropertyBool obj "ssl-strict"
setSessionSslStrict :: (MonadIO m, SessionK o) => o -> Bool -> m ()
setSessionSslStrict obj val = liftIO $ setObjectPropertyBool obj "ssl-strict" val
constructSessionSslStrict :: Bool -> IO ([Char], GValue)
constructSessionSslStrict val = constructObjectPropertyBool "ssl-strict" val
data SessionSslStrictPropertyInfo
instance AttrInfo SessionSslStrictPropertyInfo where
type AttrAllowedOps SessionSslStrictPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionSslStrictPropertyInfo = (~) Bool
type AttrBaseTypeConstraint SessionSslStrictPropertyInfo = SessionK
type AttrGetType SessionSslStrictPropertyInfo = Bool
type AttrLabel SessionSslStrictPropertyInfo = "Session::ssl-strict"
attrGet _ = getSessionSslStrict
attrSet _ = setSessionSslStrict
attrConstruct _ = constructSessionSslStrict
getSessionSslUseSystemCaFile :: (MonadIO m, SessionK o) => o -> m Bool
getSessionSslUseSystemCaFile obj = liftIO $ getObjectPropertyBool obj "ssl-use-system-ca-file"
setSessionSslUseSystemCaFile :: (MonadIO m, SessionK o) => o -> Bool -> m ()
setSessionSslUseSystemCaFile obj val = liftIO $ setObjectPropertyBool obj "ssl-use-system-ca-file" val
constructSessionSslUseSystemCaFile :: Bool -> IO ([Char], GValue)
constructSessionSslUseSystemCaFile val = constructObjectPropertyBool "ssl-use-system-ca-file" val
data SessionSslUseSystemCaFilePropertyInfo
instance AttrInfo SessionSslUseSystemCaFilePropertyInfo where
type AttrAllowedOps SessionSslUseSystemCaFilePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionSslUseSystemCaFilePropertyInfo = (~) Bool
type AttrBaseTypeConstraint SessionSslUseSystemCaFilePropertyInfo = SessionK
type AttrGetType SessionSslUseSystemCaFilePropertyInfo = Bool
type AttrLabel SessionSslUseSystemCaFilePropertyInfo = "Session::ssl-use-system-ca-file"
attrGet _ = getSessionSslUseSystemCaFile
attrSet _ = setSessionSslUseSystemCaFile
attrConstruct _ = constructSessionSslUseSystemCaFile
getSessionTimeout :: (MonadIO m, SessionK o) => o -> m Word32
getSessionTimeout obj = liftIO $ getObjectPropertyCUInt obj "timeout"
setSessionTimeout :: (MonadIO m, SessionK o) => o -> Word32 -> m ()
setSessionTimeout obj val = liftIO $ setObjectPropertyCUInt obj "timeout" val
constructSessionTimeout :: Word32 -> IO ([Char], GValue)
constructSessionTimeout val = constructObjectPropertyCUInt "timeout" val
data SessionTimeoutPropertyInfo
instance AttrInfo SessionTimeoutPropertyInfo where
type AttrAllowedOps SessionTimeoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionTimeoutPropertyInfo = (~) Word32
type AttrBaseTypeConstraint SessionTimeoutPropertyInfo = SessionK
type AttrGetType SessionTimeoutPropertyInfo = Word32
type AttrLabel SessionTimeoutPropertyInfo = "Session::timeout"
attrGet _ = getSessionTimeout
attrSet _ = setSessionTimeout
attrConstruct _ = constructSessionTimeout
getSessionTlsDatabase :: (MonadIO m, SessionK o) => o -> m Gio.TlsDatabase
getSessionTlsDatabase obj = liftIO $ getObjectPropertyObject obj "tls-database" Gio.TlsDatabase
setSessionTlsDatabase :: (MonadIO m, SessionK o, Gio.TlsDatabaseK a) => o -> a -> m ()
setSessionTlsDatabase obj val = liftIO $ setObjectPropertyObject obj "tls-database" val
constructSessionTlsDatabase :: (Gio.TlsDatabaseK a) => a -> IO ([Char], GValue)
constructSessionTlsDatabase val = constructObjectPropertyObject "tls-database" val
data SessionTlsDatabasePropertyInfo
instance AttrInfo SessionTlsDatabasePropertyInfo where
type AttrAllowedOps SessionTlsDatabasePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionTlsDatabasePropertyInfo = Gio.TlsDatabaseK
type AttrBaseTypeConstraint SessionTlsDatabasePropertyInfo = SessionK
type AttrGetType SessionTlsDatabasePropertyInfo = Gio.TlsDatabase
type AttrLabel SessionTlsDatabasePropertyInfo = "Session::tls-database"
attrGet _ = getSessionTlsDatabase
attrSet _ = setSessionTlsDatabase
attrConstruct _ = constructSessionTlsDatabase
getSessionTlsInteraction :: (MonadIO m, SessionK o) => o -> m Gio.TlsInteraction
getSessionTlsInteraction obj = liftIO $ getObjectPropertyObject obj "tls-interaction" Gio.TlsInteraction
setSessionTlsInteraction :: (MonadIO m, SessionK o, Gio.TlsInteractionK a) => o -> a -> m ()
setSessionTlsInteraction obj val = liftIO $ setObjectPropertyObject obj "tls-interaction" val
constructSessionTlsInteraction :: (Gio.TlsInteractionK a) => a -> IO ([Char], GValue)
constructSessionTlsInteraction val = constructObjectPropertyObject "tls-interaction" val
data SessionTlsInteractionPropertyInfo
instance AttrInfo SessionTlsInteractionPropertyInfo where
type AttrAllowedOps SessionTlsInteractionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionTlsInteractionPropertyInfo = Gio.TlsInteractionK
type AttrBaseTypeConstraint SessionTlsInteractionPropertyInfo = SessionK
type AttrGetType SessionTlsInteractionPropertyInfo = Gio.TlsInteraction
type AttrLabel SessionTlsInteractionPropertyInfo = "Session::tls-interaction"
attrGet _ = getSessionTlsInteraction
attrSet _ = setSessionTlsInteraction
attrConstruct _ = constructSessionTlsInteraction
getSessionUseNtlm :: (MonadIO m, SessionK o) => o -> m Bool
getSessionUseNtlm obj = liftIO $ getObjectPropertyBool obj "use-ntlm"
setSessionUseNtlm :: (MonadIO m, SessionK o) => o -> Bool -> m ()
setSessionUseNtlm obj val = liftIO $ setObjectPropertyBool obj "use-ntlm" val
constructSessionUseNtlm :: Bool -> IO ([Char], GValue)
constructSessionUseNtlm val = constructObjectPropertyBool "use-ntlm" val
data SessionUseNtlmPropertyInfo
instance AttrInfo SessionUseNtlmPropertyInfo where
type AttrAllowedOps SessionUseNtlmPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionUseNtlmPropertyInfo = (~) Bool
type AttrBaseTypeConstraint SessionUseNtlmPropertyInfo = SessionK
type AttrGetType SessionUseNtlmPropertyInfo = Bool
type AttrLabel SessionUseNtlmPropertyInfo = "Session::use-ntlm"
attrGet _ = getSessionUseNtlm
attrSet _ = setSessionUseNtlm
attrConstruct _ = constructSessionUseNtlm
getSessionUseThreadContext :: (MonadIO m, SessionK o) => o -> m Bool
getSessionUseThreadContext obj = liftIO $ getObjectPropertyBool obj "use-thread-context"
setSessionUseThreadContext :: (MonadIO m, SessionK o) => o -> Bool -> m ()
setSessionUseThreadContext obj val = liftIO $ setObjectPropertyBool obj "use-thread-context" val
constructSessionUseThreadContext :: Bool -> IO ([Char], GValue)
constructSessionUseThreadContext val = constructObjectPropertyBool "use-thread-context" val
data SessionUseThreadContextPropertyInfo
instance AttrInfo SessionUseThreadContextPropertyInfo where
type AttrAllowedOps SessionUseThreadContextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionUseThreadContextPropertyInfo = (~) Bool
type AttrBaseTypeConstraint SessionUseThreadContextPropertyInfo = SessionK
type AttrGetType SessionUseThreadContextPropertyInfo = Bool
type AttrLabel SessionUseThreadContextPropertyInfo = "Session::use-thread-context"
attrGet _ = getSessionUseThreadContext
attrSet _ = setSessionUseThreadContext
attrConstruct _ = constructSessionUseThreadContext
getSessionUserAgent :: (MonadIO m, SessionK o) => o -> m T.Text
getSessionUserAgent obj = liftIO $ getObjectPropertyString obj "user-agent"
setSessionUserAgent :: (MonadIO m, SessionK o) => o -> T.Text -> m ()
setSessionUserAgent obj val = liftIO $ setObjectPropertyString obj "user-agent" val
constructSessionUserAgent :: T.Text -> IO ([Char], GValue)
constructSessionUserAgent val = constructObjectPropertyString "user-agent" val
data SessionUserAgentPropertyInfo
instance AttrInfo SessionUserAgentPropertyInfo where
type AttrAllowedOps SessionUserAgentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint SessionUserAgentPropertyInfo = (~) T.Text
type AttrBaseTypeConstraint SessionUserAgentPropertyInfo = SessionK
type AttrGetType SessionUserAgentPropertyInfo = T.Text
type AttrLabel SessionUserAgentPropertyInfo = "Session::user-agent"
attrGet _ = getSessionUserAgent
attrSet _ = setSessionUserAgent
attrConstruct _ = constructSessionUserAgent
type instance AttributeList Session = SessionAttributeList
type SessionAttributeList = ('[ '("accept-language", SessionAcceptLanguagePropertyInfo), '("accept-language-auto", SessionAcceptLanguageAutoPropertyInfo), '("async-context", SessionAsyncContextPropertyInfo), '("http-aliases", SessionHttpAliasesPropertyInfo), '("https-aliases", SessionHttpsAliasesPropertyInfo), '("idle-timeout", SessionIdleTimeoutPropertyInfo), '("local-address", SessionLocalAddressPropertyInfo), '("max-conns", SessionMaxConnsPropertyInfo), '("max-conns-per-host", SessionMaxConnsPerHostPropertyInfo), '("proxy-resolver", SessionProxyResolverPropertyInfo), '("proxy-uri", SessionProxyUriPropertyInfo), '("ssl-ca-file", SessionSslCaFilePropertyInfo), '("ssl-strict", SessionSslStrictPropertyInfo), '("ssl-use-system-ca-file", SessionSslUseSystemCaFilePropertyInfo), '("timeout", SessionTimeoutPropertyInfo), '("tls-database", SessionTlsDatabasePropertyInfo), '("tls-interaction", SessionTlsInteractionPropertyInfo), '("use-ntlm", SessionUseNtlmPropertyInfo), '("use-thread-context", SessionUseThreadContextPropertyInfo), '("user-agent", SessionUserAgentPropertyInfo)] :: [(Symbol, *)])
data SessionAuthenticateSignalInfo
instance SignalInfo SessionAuthenticateSignalInfo where
type HaskellCallbackType SessionAuthenticateSignalInfo = SessionAuthenticateCallback
connectSignal _ = connectSessionAuthenticate
data SessionConnectionCreatedSignalInfo
instance SignalInfo SessionConnectionCreatedSignalInfo where
type HaskellCallbackType SessionConnectionCreatedSignalInfo = SessionConnectionCreatedCallback
connectSignal _ = connectSessionConnectionCreated
data SessionRequestQueuedSignalInfo
instance SignalInfo SessionRequestQueuedSignalInfo where
type HaskellCallbackType SessionRequestQueuedSignalInfo = SessionRequestQueuedCallback
connectSignal _ = connectSessionRequestQueued
data SessionRequestStartedSignalInfo
instance SignalInfo SessionRequestStartedSignalInfo where
type HaskellCallbackType SessionRequestStartedSignalInfo = SessionRequestStartedCallback
connectSignal _ = connectSessionRequestStarted
data SessionRequestUnqueuedSignalInfo
instance SignalInfo SessionRequestUnqueuedSignalInfo where
type HaskellCallbackType SessionRequestUnqueuedSignalInfo = SessionRequestUnqueuedCallback
connectSignal _ = connectSessionRequestUnqueued
data SessionTunnelingSignalInfo
instance SignalInfo SessionTunnelingSignalInfo where
type HaskellCallbackType SessionTunnelingSignalInfo = SessionTunnelingCallback
connectSignal _ = connectSessionTunneling
type instance SignalList Session = SessionSignalList
type SessionSignalList = ('[ '("authenticate", SessionAuthenticateSignalInfo), '("connection-created", SessionConnectionCreatedSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("request-queued", SessionRequestQueuedSignalInfo), '("request-started", SessionRequestStartedSignalInfo), '("request-unqueued", SessionRequestUnqueuedSignalInfo), '("tunneling", SessionTunnelingSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])
foreign import ccall "soup_session_new" soup_session_new ::
IO (Ptr Session)
sessionNew ::
(MonadIO m) =>
m Session
sessionNew = liftIO $ do
result <- soup_session_new
checkUnexpectedReturnNULL "soup_session_new" result
result' <- (wrapObject Session) result
return result'
foreign import ccall "soup_session_abort" soup_session_abort ::
Ptr Session ->
IO ()
sessionAbort ::
(MonadIO m, SessionK a) =>
a ->
m ()
sessionAbort _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
soup_session_abort _obj'
touchManagedPtr _obj
return ()
foreign import ccall "soup_session_add_feature" soup_session_add_feature ::
Ptr Session ->
Ptr SessionFeature ->
IO ()
sessionAddFeature ::
(MonadIO m, SessionK a, SessionFeatureK b) =>
a ->
b ->
m ()
sessionAddFeature _obj feature = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let feature' = unsafeManagedPtrCastPtr feature
soup_session_add_feature _obj' feature'
touchManagedPtr _obj
touchManagedPtr feature
return ()
foreign import ccall "soup_session_add_feature_by_type" soup_session_add_feature_by_type ::
Ptr Session ->
CGType ->
IO ()
sessionAddFeatureByType ::
(MonadIO m, SessionK a) =>
a ->
GType ->
m ()
sessionAddFeatureByType _obj feature_type = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let feature_type' = gtypeToCGType feature_type
soup_session_add_feature_by_type _obj' feature_type'
touchManagedPtr _obj
return ()
foreign import ccall "soup_session_cancel_message" soup_session_cancel_message ::
Ptr Session ->
Ptr Message ->
Word32 ->
IO ()
sessionCancelMessage ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
Word32 ->
m ()
sessionCancelMessage _obj msg status_code = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
soup_session_cancel_message _obj' msg' status_code
touchManagedPtr _obj
touchManagedPtr msg
return ()
foreign import ccall "soup_session_get_async_context" soup_session_get_async_context ::
Ptr Session ->
IO (Ptr GLib.MainContext)
sessionGetAsyncContext ::
(MonadIO m, SessionK a) =>
a ->
m GLib.MainContext
sessionGetAsyncContext _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- soup_session_get_async_context _obj'
checkUnexpectedReturnNULL "soup_session_get_async_context" result
result' <- (newBoxed GLib.MainContext) result
touchManagedPtr _obj
return result'
foreign import ccall "soup_session_get_feature" soup_session_get_feature ::
Ptr Session ->
CGType ->
IO (Ptr SessionFeature)
sessionGetFeature ::
(MonadIO m, SessionK a) =>
a ->
GType ->
m SessionFeature
sessionGetFeature _obj feature_type = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let feature_type' = gtypeToCGType feature_type
result <- soup_session_get_feature _obj' feature_type'
checkUnexpectedReturnNULL "soup_session_get_feature" result
result' <- (newObject SessionFeature) result
touchManagedPtr _obj
return result'
foreign import ccall "soup_session_get_feature_for_message" soup_session_get_feature_for_message ::
Ptr Session ->
CGType ->
Ptr Message ->
IO (Ptr SessionFeature)
sessionGetFeatureForMessage ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
GType ->
b ->
m SessionFeature
sessionGetFeatureForMessage _obj feature_type msg = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let feature_type' = gtypeToCGType feature_type
let msg' = unsafeManagedPtrCastPtr msg
result <- soup_session_get_feature_for_message _obj' feature_type' msg'
checkUnexpectedReturnNULL "soup_session_get_feature_for_message" result
result' <- (newObject SessionFeature) result
touchManagedPtr _obj
touchManagedPtr msg
return result'
foreign import ccall "soup_session_get_features" soup_session_get_features ::
Ptr Session ->
CGType ->
IO (Ptr (GSList (Ptr SessionFeature)))
sessionGetFeatures ::
(MonadIO m, SessionK a) =>
a ->
GType ->
m [SessionFeature]
sessionGetFeatures _obj feature_type = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let feature_type' = gtypeToCGType feature_type
result <- soup_session_get_features _obj' feature_type'
checkUnexpectedReturnNULL "soup_session_get_features" result
result' <- unpackGSList result
result'' <- mapM (newObject SessionFeature) result'
g_slist_free result
touchManagedPtr _obj
return result''
foreign import ccall "soup_session_has_feature" soup_session_has_feature ::
Ptr Session ->
CGType ->
IO CInt
sessionHasFeature ::
(MonadIO m, SessionK a) =>
a ->
GType ->
m Bool
sessionHasFeature _obj feature_type = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let feature_type' = gtypeToCGType feature_type
result <- soup_session_has_feature _obj' feature_type'
let result' = (/= 0) result
touchManagedPtr _obj
return result'
foreign import ccall "soup_session_pause_message" soup_session_pause_message ::
Ptr Session ->
Ptr Message ->
IO ()
sessionPauseMessage ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
m ()
sessionPauseMessage _obj msg = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
soup_session_pause_message _obj' msg'
touchManagedPtr _obj
touchManagedPtr msg
return ()
foreign import ccall "soup_session_prefetch_dns" soup_session_prefetch_dns ::
Ptr Session ->
CString ->
Ptr Gio.Cancellable ->
FunPtr AddressCallbackC ->
Ptr () ->
IO ()
sessionPrefetchDns ::
(MonadIO m, SessionK a, Gio.CancellableK b) =>
a ->
T.Text ->
Maybe (b) ->
Maybe (AddressCallback) ->
m ()
sessionPrefetchDns _obj hostname cancellable callback = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
hostname' <- textToCString hostname
maybeCancellable <- case cancellable of
Nothing -> return nullPtr
Just jCancellable -> do
let jCancellable' = unsafeManagedPtrCastPtr jCancellable
return jCancellable'
ptrcallback <- callocMem :: IO (Ptr (FunPtr AddressCallbackC))
maybeCallback <- case callback of
Nothing -> return (castPtrToFunPtr nullPtr)
Just jCallback -> do
jCallback' <- mkAddressCallback (addressCallbackWrapper (Just ptrcallback) jCallback)
poke ptrcallback jCallback'
return jCallback'
let user_data = nullPtr
soup_session_prefetch_dns _obj' hostname' maybeCancellable maybeCallback user_data
touchManagedPtr _obj
whenJust cancellable touchManagedPtr
freeMem hostname'
return ()
foreign import ccall "soup_session_prepare_for_uri" soup_session_prepare_for_uri ::
Ptr Session ->
Ptr URI ->
IO ()
sessionPrepareForUri ::
(MonadIO m, SessionK a) =>
a ->
URI ->
m ()
sessionPrepareForUri _obj uri = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let uri' = unsafeManagedPtrGetPtr uri
soup_session_prepare_for_uri _obj' uri'
touchManagedPtr _obj
touchManagedPtr uri
return ()
foreign import ccall "soup_session_queue_message" soup_session_queue_message ::
Ptr Session ->
Ptr Message ->
FunPtr SessionCallbackC ->
Ptr () ->
IO ()
sessionQueueMessage ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
Maybe (SessionCallback) ->
m ()
sessionQueueMessage _obj msg callback = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
msg' <- refObject msg
ptrcallback <- callocMem :: IO (Ptr (FunPtr SessionCallbackC))
maybeCallback <- case callback of
Nothing -> return (castPtrToFunPtr nullPtr)
Just jCallback -> do
jCallback' <- mkSessionCallback (sessionCallbackWrapper (Just ptrcallback) jCallback)
poke ptrcallback jCallback'
return jCallback'
let user_data = nullPtr
soup_session_queue_message _obj' msg' maybeCallback user_data
touchManagedPtr _obj
touchManagedPtr msg
return ()
foreign import ccall "soup_session_redirect_message" soup_session_redirect_message ::
Ptr Session ->
Ptr Message ->
IO CInt
sessionRedirectMessage ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
m Bool
sessionRedirectMessage _obj msg = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
result <- soup_session_redirect_message _obj' msg'
let result' = (/= 0) result
touchManagedPtr _obj
touchManagedPtr msg
return result'
foreign import ccall "soup_session_remove_feature" soup_session_remove_feature ::
Ptr Session ->
Ptr SessionFeature ->
IO ()
sessionRemoveFeature ::
(MonadIO m, SessionK a, SessionFeatureK b) =>
a ->
b ->
m ()
sessionRemoveFeature _obj feature = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let feature' = unsafeManagedPtrCastPtr feature
soup_session_remove_feature _obj' feature'
touchManagedPtr _obj
touchManagedPtr feature
return ()
foreign import ccall "soup_session_remove_feature_by_type" soup_session_remove_feature_by_type ::
Ptr Session ->
CGType ->
IO ()
sessionRemoveFeatureByType ::
(MonadIO m, SessionK a) =>
a ->
GType ->
m ()
sessionRemoveFeatureByType _obj feature_type = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let feature_type' = gtypeToCGType feature_type
soup_session_remove_feature_by_type _obj' feature_type'
touchManagedPtr _obj
return ()
foreign import ccall "soup_session_request" soup_session_request ::
Ptr Session ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr Request)
sessionRequest ::
(MonadIO m, SessionK a) =>
a ->
T.Text ->
m Request
sessionRequest _obj uri_string = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
uri_string' <- textToCString uri_string
onException (do
result <- propagateGError $ soup_session_request _obj' uri_string'
checkUnexpectedReturnNULL "soup_session_request" result
result' <- (wrapObject Request) result
touchManagedPtr _obj
freeMem uri_string'
return result'
) (do
freeMem uri_string'
)
foreign import ccall "soup_session_request_http" soup_session_request_http ::
Ptr Session ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr RequestHTTP)
sessionRequestHttp ::
(MonadIO m, SessionK a) =>
a ->
T.Text ->
T.Text ->
m RequestHTTP
sessionRequestHttp _obj method uri_string = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
method' <- textToCString method
uri_string' <- textToCString uri_string
onException (do
result <- propagateGError $ soup_session_request_http _obj' method' uri_string'
checkUnexpectedReturnNULL "soup_session_request_http" result
result' <- (wrapObject RequestHTTP) result
touchManagedPtr _obj
freeMem method'
freeMem uri_string'
return result'
) (do
freeMem method'
freeMem uri_string'
)
foreign import ccall "soup_session_request_http_uri" soup_session_request_http_uri ::
Ptr Session ->
CString ->
Ptr URI ->
Ptr (Ptr GError) ->
IO (Ptr RequestHTTP)
sessionRequestHttpUri ::
(MonadIO m, SessionK a) =>
a ->
T.Text ->
URI ->
m RequestHTTP
sessionRequestHttpUri _obj method uri = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
method' <- textToCString method
let uri' = unsafeManagedPtrGetPtr uri
onException (do
result <- propagateGError $ soup_session_request_http_uri _obj' method' uri'
checkUnexpectedReturnNULL "soup_session_request_http_uri" result
result' <- (wrapObject RequestHTTP) result
touchManagedPtr _obj
touchManagedPtr uri
freeMem method'
return result'
) (do
freeMem method'
)
foreign import ccall "soup_session_request_uri" soup_session_request_uri ::
Ptr Session ->
Ptr URI ->
Ptr (Ptr GError) ->
IO (Ptr Request)
sessionRequestUri ::
(MonadIO m, SessionK a) =>
a ->
URI ->
m Request
sessionRequestUri _obj uri = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let uri' = unsafeManagedPtrGetPtr uri
onException (do
result <- propagateGError $ soup_session_request_uri _obj' uri'
checkUnexpectedReturnNULL "soup_session_request_uri" result
result' <- (wrapObject Request) result
touchManagedPtr _obj
touchManagedPtr uri
return result'
) (do
return ()
)
foreign import ccall "soup_session_requeue_message" soup_session_requeue_message ::
Ptr Session ->
Ptr Message ->
IO ()
sessionRequeueMessage ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
m ()
sessionRequeueMessage _obj msg = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
soup_session_requeue_message _obj' msg'
touchManagedPtr _obj
touchManagedPtr msg
return ()
foreign import ccall "soup_session_send" soup_session_send ::
Ptr Session ->
Ptr Message ->
Ptr Gio.Cancellable ->
Ptr (Ptr GError) ->
IO (Ptr Gio.InputStream)
sessionSend ::
(MonadIO m, SessionK a, MessageK b, Gio.CancellableK c) =>
a ->
b ->
Maybe (c) ->
m Gio.InputStream
sessionSend _obj msg cancellable = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
maybeCancellable <- case cancellable of
Nothing -> return nullPtr
Just jCancellable -> do
let jCancellable' = unsafeManagedPtrCastPtr jCancellable
return jCancellable'
onException (do
result <- propagateGError $ soup_session_send _obj' msg' maybeCancellable
checkUnexpectedReturnNULL "soup_session_send" result
result' <- (wrapObject Gio.InputStream) result
touchManagedPtr _obj
touchManagedPtr msg
whenJust cancellable touchManagedPtr
return result'
) (do
return ()
)
foreign import ccall "soup_session_send_async" soup_session_send_async ::
Ptr Session ->
Ptr Message ->
Ptr Gio.Cancellable ->
FunPtr Gio.AsyncReadyCallbackC ->
Ptr () ->
IO ()
sessionSendAsync ::
(MonadIO m, SessionK a, MessageK b, Gio.CancellableK c) =>
a ->
b ->
Maybe (c) ->
Maybe (Gio.AsyncReadyCallback) ->
m ()
sessionSendAsync _obj msg cancellable callback = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
maybeCancellable <- case cancellable of
Nothing -> return nullPtr
Just jCancellable -> do
let jCancellable' = unsafeManagedPtrCastPtr jCancellable
return jCancellable'
ptrcallback <- callocMem :: IO (Ptr (FunPtr Gio.AsyncReadyCallbackC))
maybeCallback <- case callback of
Nothing -> return (castPtrToFunPtr nullPtr)
Just jCallback -> do
jCallback' <- Gio.mkAsyncReadyCallback (Gio.asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
poke ptrcallback jCallback'
return jCallback'
let user_data = nullPtr
soup_session_send_async _obj' msg' maybeCancellable maybeCallback user_data
touchManagedPtr _obj
touchManagedPtr msg
whenJust cancellable touchManagedPtr
return ()
foreign import ccall "soup_session_send_finish" soup_session_send_finish ::
Ptr Session ->
Ptr Gio.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr Gio.InputStream)
sessionSendFinish ::
(MonadIO m, SessionK a, Gio.AsyncResultK b) =>
a ->
b ->
m Gio.InputStream
sessionSendFinish _obj result_ = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let result_' = unsafeManagedPtrCastPtr result_
onException (do
result <- propagateGError $ soup_session_send_finish _obj' result_'
checkUnexpectedReturnNULL "soup_session_send_finish" result
result' <- (wrapObject Gio.InputStream) result
touchManagedPtr _obj
touchManagedPtr result_
return result'
) (do
return ()
)
foreign import ccall "soup_session_send_message" soup_session_send_message ::
Ptr Session ->
Ptr Message ->
IO Word32
sessionSendMessage ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
m Word32
sessionSendMessage _obj msg = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
result <- soup_session_send_message _obj' msg'
touchManagedPtr _obj
touchManagedPtr msg
return result
foreign import ccall "soup_session_steal_connection" soup_session_steal_connection ::
Ptr Session ->
Ptr Message ->
IO (Ptr Gio.IOStream)
sessionStealConnection ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
m Gio.IOStream
sessionStealConnection _obj msg = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
result <- soup_session_steal_connection _obj' msg'
checkUnexpectedReturnNULL "soup_session_steal_connection" result
result' <- (wrapObject Gio.IOStream) result
touchManagedPtr _obj
touchManagedPtr msg
return result'
foreign import ccall "soup_session_unpause_message" soup_session_unpause_message ::
Ptr Session ->
Ptr Message ->
IO ()
sessionUnpauseMessage ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
m ()
sessionUnpauseMessage _obj msg = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
soup_session_unpause_message _obj' msg'
touchManagedPtr _obj
touchManagedPtr msg
return ()
foreign import ccall "soup_session_websocket_connect_async" soup_session_websocket_connect_async ::
Ptr Session ->
Ptr Message ->
CString ->
Ptr CString ->
Ptr Gio.Cancellable ->
FunPtr Gio.AsyncReadyCallbackC ->
Ptr () ->
IO ()
sessionWebsocketConnectAsync ::
(MonadIO m, SessionK a, MessageK b, Gio.CancellableK c) =>
a ->
b ->
Maybe (T.Text) ->
Maybe ([T.Text]) ->
Maybe (c) ->
Maybe (Gio.AsyncReadyCallback) ->
m ()
sessionWebsocketConnectAsync _obj msg origin protocols cancellable callback = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
maybeOrigin <- case origin of
Nothing -> return nullPtr
Just jOrigin -> do
jOrigin' <- textToCString jOrigin
return jOrigin'
maybeProtocols <- case protocols of
Nothing -> return nullPtr
Just jProtocols -> do
jProtocols' <- packZeroTerminatedUTF8CArray jProtocols
return jProtocols'
maybeCancellable <- case cancellable of
Nothing -> return nullPtr
Just jCancellable -> do
let jCancellable' = unsafeManagedPtrCastPtr jCancellable
return jCancellable'
ptrcallback <- callocMem :: IO (Ptr (FunPtr Gio.AsyncReadyCallbackC))
maybeCallback <- case callback of
Nothing -> return (castPtrToFunPtr nullPtr)
Just jCallback -> do
jCallback' <- Gio.mkAsyncReadyCallback (Gio.asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
poke ptrcallback jCallback'
return jCallback'
let user_data = nullPtr
soup_session_websocket_connect_async _obj' msg' maybeOrigin maybeProtocols maybeCancellable maybeCallback user_data
touchManagedPtr _obj
touchManagedPtr msg
whenJust cancellable touchManagedPtr
freeMem maybeOrigin
mapZeroTerminatedCArray freeMem maybeProtocols
freeMem maybeProtocols
return ()
foreign import ccall "soup_session_websocket_connect_finish" soup_session_websocket_connect_finish ::
Ptr Session ->
Ptr Gio.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr WebsocketConnection)
sessionWebsocketConnectFinish ::
(MonadIO m, SessionK a, Gio.AsyncResultK b) =>
a ->
b ->
m WebsocketConnection
sessionWebsocketConnectFinish _obj result_ = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let result_' = unsafeManagedPtrCastPtr result_
onException (do
result <- propagateGError $ soup_session_websocket_connect_finish _obj' result_'
checkUnexpectedReturnNULL "soup_session_websocket_connect_finish" result
result' <- (wrapObject WebsocketConnection) result
touchManagedPtr _obj
touchManagedPtr result_
return result'
) (do
return ()
)
foreign import ccall "soup_session_would_redirect" soup_session_would_redirect ::
Ptr Session ->
Ptr Message ->
IO CInt
sessionWouldRedirect ::
(MonadIO m, SessionK a, MessageK b) =>
a ->
b ->
m Bool
sessionWouldRedirect _obj msg = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let msg' = unsafeManagedPtrCastPtr msg
result <- soup_session_would_redirect _obj' msg'
let result' = (/= 0) result
touchManagedPtr _obj
touchManagedPtr msg
return result'