{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Soup.Objects.SessionAsync
    ( 

-- * Exported types
    SessionAsync(..)                        ,
    IsSessionAsync                          ,
    toSessionAsync                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [abort]("GI.Soup.Objects.Session#g:method:abort"), [addFeature]("GI.Soup.Objects.Session#g:method:addFeature"), [addFeatureByType]("GI.Soup.Objects.Session#g:method:addFeatureByType"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [cancelMessage]("GI.Soup.Objects.Session#g:method:cancelMessage"), [connectAsync]("GI.Soup.Objects.Session#g:method:connectAsync"), [connectFinish]("GI.Soup.Objects.Session#g:method:connectFinish"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasFeature]("GI.Soup.Objects.Session#g:method:hasFeature"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [pauseMessage]("GI.Soup.Objects.Session#g:method:pauseMessage"), [prefetchDns]("GI.Soup.Objects.Session#g:method:prefetchDns"), [prepareForUri]("GI.Soup.Objects.Session#g:method:prepareForUri"), [queueMessage]("GI.Soup.Objects.Session#g:method:queueMessage"), [redirectMessage]("GI.Soup.Objects.Session#g:method:redirectMessage"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeFeature]("GI.Soup.Objects.Session#g:method:removeFeature"), [removeFeatureByType]("GI.Soup.Objects.Session#g:method:removeFeatureByType"), [request]("GI.Soup.Objects.Session#g:method:request"), [requestHttp]("GI.Soup.Objects.Session#g:method:requestHttp"), [requestHttpUri]("GI.Soup.Objects.Session#g:method:requestHttpUri"), [requestUri]("GI.Soup.Objects.Session#g:method:requestUri"), [requeueMessage]("GI.Soup.Objects.Session#g:method:requeueMessage"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [send]("GI.Soup.Objects.Session#g:method:send"), [sendAsync]("GI.Soup.Objects.Session#g:method:sendAsync"), [sendFinish]("GI.Soup.Objects.Session#g:method:sendFinish"), [sendMessage]("GI.Soup.Objects.Session#g:method:sendMessage"), [stealConnection]("GI.Soup.Objects.Session#g:method:stealConnection"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unpauseMessage]("GI.Soup.Objects.Session#g:method:unpauseMessage"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure"), [websocketConnectAsync]("GI.Soup.Objects.Session#g:method:websocketConnectAsync"), [websocketConnectFinish]("GI.Soup.Objects.Session#g:method:websocketConnectFinish"), [wouldRedirect]("GI.Soup.Objects.Session#g:method:wouldRedirect").
-- 
-- ==== Getters
-- [getAsyncContext]("GI.Soup.Objects.Session#g:method:getAsyncContext"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFeature]("GI.Soup.Objects.Session#g:method:getFeature"), [getFeatureForMessage]("GI.Soup.Objects.Session#g:method:getFeatureForMessage"), [getFeatures]("GI.Soup.Objects.Session#g:method:getFeatures"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveSessionAsyncMethod               ,
#endif

-- ** new #method:new#

    sessionAsyncNew                         ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Soup.Objects.Session as Soup.Session

-- | Memory-managed wrapper type.
newtype SessionAsync = SessionAsync (SP.ManagedPtr SessionAsync)
    deriving (SessionAsync -> SessionAsync -> Bool
(SessionAsync -> SessionAsync -> Bool)
-> (SessionAsync -> SessionAsync -> Bool) -> Eq SessionAsync
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SessionAsync -> SessionAsync -> Bool
== :: SessionAsync -> SessionAsync -> Bool
$c/= :: SessionAsync -> SessionAsync -> Bool
/= :: SessionAsync -> SessionAsync -> Bool
Eq)

instance SP.ManagedPtrNewtype SessionAsync where
    toManagedPtr :: SessionAsync -> ManagedPtr SessionAsync
toManagedPtr (SessionAsync ManagedPtr SessionAsync
p) = ManagedPtr SessionAsync
p

foreign import ccall "soup_session_async_get_type"
    c_soup_session_async_get_type :: IO B.Types.GType

instance B.Types.TypedObject SessionAsync where
    glibType :: IO GType
glibType = IO GType
c_soup_session_async_get_type

instance B.Types.GObject SessionAsync

-- | Type class for types which can be safely cast to `SessionAsync`, for instance with `toSessionAsync`.
class (SP.GObject o, O.IsDescendantOf SessionAsync o) => IsSessionAsync o
instance (SP.GObject o, O.IsDescendantOf SessionAsync o) => IsSessionAsync o

instance O.HasParentTypes SessionAsync
type instance O.ParentTypes SessionAsync = '[Soup.Session.Session, GObject.Object.Object]

-- | Cast to `SessionAsync`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toSessionAsync :: (MIO.MonadIO m, IsSessionAsync o) => o -> m SessionAsync
toSessionAsync :: forall (m :: * -> *) o.
(MonadIO m, IsSessionAsync o) =>
o -> m SessionAsync
toSessionAsync = IO SessionAsync -> m SessionAsync
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SessionAsync -> m SessionAsync)
-> (o -> IO SessionAsync) -> o -> m SessionAsync
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SessionAsync -> SessionAsync) -> o -> IO SessionAsync
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr SessionAsync -> SessionAsync
SessionAsync

-- | Convert 'SessionAsync' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe SessionAsync) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_soup_session_async_get_type
    gvalueSet_ :: Ptr GValue -> Maybe SessionAsync -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SessionAsync
P.Nothing = Ptr GValue -> Ptr SessionAsync -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SessionAsync
forall a. Ptr a
FP.nullPtr :: FP.Ptr SessionAsync)
    gvalueSet_ Ptr GValue
gv (P.Just SessionAsync
obj) = SessionAsync -> (Ptr SessionAsync -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SessionAsync
obj (Ptr GValue -> Ptr SessionAsync -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe SessionAsync)
gvalueGet_ Ptr GValue
gv = do
        Ptr SessionAsync
ptr <- Ptr GValue -> IO (Ptr SessionAsync)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SessionAsync)
        if Ptr SessionAsync
ptr Ptr SessionAsync -> Ptr SessionAsync -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr SessionAsync
forall a. Ptr a
FP.nullPtr
        then SessionAsync -> Maybe SessionAsync
forall a. a -> Maybe a
P.Just (SessionAsync -> Maybe SessionAsync)
-> IO SessionAsync -> IO (Maybe SessionAsync)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr SessionAsync -> SessionAsync)
-> Ptr SessionAsync -> IO SessionAsync
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SessionAsync -> SessionAsync
SessionAsync Ptr SessionAsync
ptr
        else Maybe SessionAsync -> IO (Maybe SessionAsync)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SessionAsync
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveSessionAsyncMethod (t :: Symbol) (o :: *) :: * where
    ResolveSessionAsyncMethod "abort" o = Soup.Session.SessionAbortMethodInfo
    ResolveSessionAsyncMethod "addFeature" o = Soup.Session.SessionAddFeatureMethodInfo
    ResolveSessionAsyncMethod "addFeatureByType" o = Soup.Session.SessionAddFeatureByTypeMethodInfo
    ResolveSessionAsyncMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSessionAsyncMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSessionAsyncMethod "cancelMessage" o = Soup.Session.SessionCancelMessageMethodInfo
    ResolveSessionAsyncMethod "connectAsync" o = Soup.Session.SessionConnectAsyncMethodInfo
    ResolveSessionAsyncMethod "connectFinish" o = Soup.Session.SessionConnectFinishMethodInfo
    ResolveSessionAsyncMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSessionAsyncMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSessionAsyncMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSessionAsyncMethod "hasFeature" o = Soup.Session.SessionHasFeatureMethodInfo
    ResolveSessionAsyncMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSessionAsyncMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSessionAsyncMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSessionAsyncMethod "pauseMessage" o = Soup.Session.SessionPauseMessageMethodInfo
    ResolveSessionAsyncMethod "prefetchDns" o = Soup.Session.SessionPrefetchDnsMethodInfo
    ResolveSessionAsyncMethod "prepareForUri" o = Soup.Session.SessionPrepareForUriMethodInfo
    ResolveSessionAsyncMethod "queueMessage" o = Soup.Session.SessionQueueMessageMethodInfo
    ResolveSessionAsyncMethod "redirectMessage" o = Soup.Session.SessionRedirectMessageMethodInfo
    ResolveSessionAsyncMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSessionAsyncMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSessionAsyncMethod "removeFeature" o = Soup.Session.SessionRemoveFeatureMethodInfo
    ResolveSessionAsyncMethod "removeFeatureByType" o = Soup.Session.SessionRemoveFeatureByTypeMethodInfo
    ResolveSessionAsyncMethod "request" o = Soup.Session.SessionRequestMethodInfo
    ResolveSessionAsyncMethod "requestHttp" o = Soup.Session.SessionRequestHttpMethodInfo
    ResolveSessionAsyncMethod "requestHttpUri" o = Soup.Session.SessionRequestHttpUriMethodInfo
    ResolveSessionAsyncMethod "requestUri" o = Soup.Session.SessionRequestUriMethodInfo
    ResolveSessionAsyncMethod "requeueMessage" o = Soup.Session.SessionRequeueMessageMethodInfo
    ResolveSessionAsyncMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSessionAsyncMethod "send" o = Soup.Session.SessionSendMethodInfo
    ResolveSessionAsyncMethod "sendAsync" o = Soup.Session.SessionSendAsyncMethodInfo
    ResolveSessionAsyncMethod "sendFinish" o = Soup.Session.SessionSendFinishMethodInfo
    ResolveSessionAsyncMethod "sendMessage" o = Soup.Session.SessionSendMessageMethodInfo
    ResolveSessionAsyncMethod "stealConnection" o = Soup.Session.SessionStealConnectionMethodInfo
    ResolveSessionAsyncMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSessionAsyncMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSessionAsyncMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSessionAsyncMethod "unpauseMessage" o = Soup.Session.SessionUnpauseMessageMethodInfo
    ResolveSessionAsyncMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSessionAsyncMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSessionAsyncMethod "websocketConnectAsync" o = Soup.Session.SessionWebsocketConnectAsyncMethodInfo
    ResolveSessionAsyncMethod "websocketConnectFinish" o = Soup.Session.SessionWebsocketConnectFinishMethodInfo
    ResolveSessionAsyncMethod "wouldRedirect" o = Soup.Session.SessionWouldRedirectMethodInfo
    ResolveSessionAsyncMethod "getAsyncContext" o = Soup.Session.SessionGetAsyncContextMethodInfo
    ResolveSessionAsyncMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSessionAsyncMethod "getFeature" o = Soup.Session.SessionGetFeatureMethodInfo
    ResolveSessionAsyncMethod "getFeatureForMessage" o = Soup.Session.SessionGetFeatureForMessageMethodInfo
    ResolveSessionAsyncMethod "getFeatures" o = Soup.Session.SessionGetFeaturesMethodInfo
    ResolveSessionAsyncMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSessionAsyncMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSessionAsyncMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSessionAsyncMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSessionAsyncMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSessionAsyncMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveSessionAsyncMethod t SessionAsync, O.OverloadedMethod info SessionAsync p) => OL.IsLabel t (SessionAsync -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveSessionAsyncMethod t SessionAsync, O.OverloadedMethod info SessionAsync p, R.HasField t SessionAsync p) => R.HasField t SessionAsync p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveSessionAsyncMethod t SessionAsync, O.OverloadedMethodInfo info SessionAsync) => OL.IsLabel t (O.MethodProxy info SessionAsync) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SessionAsync
type instance O.AttributeList SessionAsync = SessionAsyncAttributeList
type SessionAsyncAttributeList = ('[ '("acceptLanguage", Soup.Session.SessionAcceptLanguagePropertyInfo), '("acceptLanguageAuto", Soup.Session.SessionAcceptLanguageAutoPropertyInfo), '("asyncContext", Soup.Session.SessionAsyncContextPropertyInfo), '("httpAliases", Soup.Session.SessionHttpAliasesPropertyInfo), '("httpsAliases", Soup.Session.SessionHttpsAliasesPropertyInfo), '("idleTimeout", Soup.Session.SessionIdleTimeoutPropertyInfo), '("localAddress", Soup.Session.SessionLocalAddressPropertyInfo), '("maxConns", Soup.Session.SessionMaxConnsPropertyInfo), '("maxConnsPerHost", Soup.Session.SessionMaxConnsPerHostPropertyInfo), '("proxyResolver", Soup.Session.SessionProxyResolverPropertyInfo), '("proxyUri", Soup.Session.SessionProxyUriPropertyInfo), '("sslCaFile", Soup.Session.SessionSslCaFilePropertyInfo), '("sslStrict", Soup.Session.SessionSslStrictPropertyInfo), '("sslUseSystemCaFile", Soup.Session.SessionSslUseSystemCaFilePropertyInfo), '("timeout", Soup.Session.SessionTimeoutPropertyInfo), '("tlsDatabase", Soup.Session.SessionTlsDatabasePropertyInfo), '("tlsInteraction", Soup.Session.SessionTlsInteractionPropertyInfo), '("useNtlm", Soup.Session.SessionUseNtlmPropertyInfo), '("useThreadContext", Soup.Session.SessionUseThreadContextPropertyInfo), '("userAgent", Soup.Session.SessionUserAgentPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SessionAsync = SessionAsyncSignalList
type SessionAsyncSignalList = ('[ '("authenticate", Soup.Session.SessionAuthenticateSignalInfo), '("connectionCreated", Soup.Session.SessionConnectionCreatedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("requestQueued", Soup.Session.SessionRequestQueuedSignalInfo), '("requestStarted", Soup.Session.SessionRequestStartedSignalInfo), '("requestUnqueued", Soup.Session.SessionRequestUnqueuedSignalInfo), '("tunneling", Soup.Session.SessionTunnelingSignalInfo)] :: [(Symbol, *)])

#endif

-- method SessionAsync::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Soup" , name = "SessionAsync" })
-- throws : False
-- Skip return : False

foreign import ccall "soup_session_async_new" soup_session_async_new :: 
    IO (Ptr SessionAsync)

{-# DEPRECATED sessionAsyncNew ["t'GI.Soup.Objects.SessionAsync.SessionAsync' is deprecated; use a plain","t'GI.Soup.Objects.Session.Session', created with 'GI.Soup.Objects.Session.sessionNew'. See the \\<link","linkend=\\\"libsoup-session-porting\\\">porting guide\\<\\/link>."] #-}
-- | Creates an asynchronous t'GI.Soup.Objects.Session.Session' with the default options.
sessionAsyncNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m SessionAsync
    -- ^ __Returns:__ the new session.
sessionAsyncNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m SessionAsync
sessionAsyncNew  = IO SessionAsync -> m SessionAsync
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SessionAsync -> m SessionAsync)
-> IO SessionAsync -> m SessionAsync
forall a b. (a -> b) -> a -> b
$ do
    Ptr SessionAsync
result <- IO (Ptr SessionAsync)
soup_session_async_new
    Text -> Ptr SessionAsync -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sessionAsyncNew" Ptr SessionAsync
result
    SessionAsync
result' <- ((ManagedPtr SessionAsync -> SessionAsync)
-> Ptr SessionAsync -> IO SessionAsync
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SessionAsync -> SessionAsync
SessionAsync) Ptr SessionAsync
result
    SessionAsync -> IO SessionAsync
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SessionAsync
result'

#if defined(ENABLE_OVERLOADING)
#endif