{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.WebKit.Objects.NetworkSession
(
NetworkSession(..) ,
IsNetworkSession ,
toNetworkSession ,
#if defined(ENABLE_OVERLOADING)
ResolveNetworkSessionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkSessionAllowTlsCertificateForHostMethodInfo,
#endif
networkSessionAllowTlsCertificateForHost,
#if defined(ENABLE_OVERLOADING)
NetworkSessionDownloadUriMethodInfo ,
#endif
networkSessionDownloadUri ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionGetCookieManagerMethodInfo,
#endif
networkSessionGetCookieManager ,
networkSessionGetDefault ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionGetItpEnabledMethodInfo ,
#endif
networkSessionGetItpEnabled ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionGetItpSummaryMethodInfo ,
#endif
networkSessionGetItpSummary ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionGetItpSummaryFinishMethodInfo,
#endif
networkSessionGetItpSummaryFinish ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionGetPersistentCredentialStorageEnabledMethodInfo,
#endif
networkSessionGetPersistentCredentialStorageEnabled,
#if defined(ENABLE_OVERLOADING)
NetworkSessionGetTlsErrorsPolicyMethodInfo,
#endif
networkSessionGetTlsErrorsPolicy ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionGetWebsiteDataManagerMethodInfo,
#endif
networkSessionGetWebsiteDataManager ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionIsEphemeralMethodInfo ,
#endif
networkSessionIsEphemeral ,
networkSessionNew ,
networkSessionNewEphemeral ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionPrefetchDnsMethodInfo ,
#endif
networkSessionPrefetchDns ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionSetItpEnabledMethodInfo ,
#endif
networkSessionSetItpEnabled ,
networkSessionSetMemoryPressureSettings ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionSetPersistentCredentialStorageEnabledMethodInfo,
#endif
networkSessionSetPersistentCredentialStorageEnabled,
#if defined(ENABLE_OVERLOADING)
NetworkSessionSetProxySettingsMethodInfo,
#endif
networkSessionSetProxySettings ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionSetTlsErrorsPolicyMethodInfo,
#endif
networkSessionSetTlsErrorsPolicy ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionCacheDirectoryPropertyInfo,
#endif
constructNetworkSessionCacheDirectory ,
#if defined(ENABLE_OVERLOADING)
networkSessionCacheDirectory ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkSessionDataDirectoryPropertyInfo ,
#endif
constructNetworkSessionDataDirectory ,
#if defined(ENABLE_OVERLOADING)
networkSessionDataDirectory ,
#endif
#if defined(ENABLE_OVERLOADING)
NetworkSessionIsEphemeralPropertyInfo ,
#endif
constructNetworkSessionIsEphemeral ,
getNetworkSessionIsEphemeral ,
NetworkSessionDownloadStartedCallback ,
#if defined(ENABLE_OVERLOADING)
NetworkSessionDownloadStartedSignalInfo ,
#endif
afterNetworkSessionDownloadStarted ,
onNetworkSessionDownloadStarted ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.Action as Gio.Action
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.InputStream as Gio.InputStream
import qualified GI.Gio.Objects.TlsCertificate as Gio.TlsCertificate
import qualified GI.Gio.Objects.UnixFDList as Gio.UnixFDList
import qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import qualified GI.Gtk.Objects.FileFilter as Gtk.FileFilter
import qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
import qualified GI.Gtk.Objects.Window as Gtk.Window
import qualified GI.JavaScriptCore.Objects.Value as JavaScriptCore.Value
import qualified GI.Soup.Structs.Cookie as Soup.Cookie
import qualified GI.Soup.Structs.MessageHeaders as Soup.MessageHeaders
import qualified GI.WebKit.Callbacks as WebKit.Callbacks
import {-# SOURCE #-} qualified GI.WebKit.Enums as WebKit.Enums
import {-# SOURCE #-} qualified GI.WebKit.Flags as WebKit.Flags
import {-# SOURCE #-} qualified GI.WebKit.Interfaces.PermissionRequest as WebKit.PermissionRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.AuthenticationRequest as WebKit.AuthenticationRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.AutomationSession as WebKit.AutomationSession
import {-# SOURCE #-} qualified GI.WebKit.Objects.BackForwardList as WebKit.BackForwardList
import {-# SOURCE #-} qualified GI.WebKit.Objects.BackForwardListItem as WebKit.BackForwardListItem
import {-# SOURCE #-} qualified GI.WebKit.Objects.ColorChooserRequest as WebKit.ColorChooserRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.ContextMenu as WebKit.ContextMenu
import {-# SOURCE #-} qualified GI.WebKit.Objects.ContextMenuItem as WebKit.ContextMenuItem
import {-# SOURCE #-} qualified GI.WebKit.Objects.CookieManager as WebKit.CookieManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.Download as WebKit.Download
import {-# SOURCE #-} qualified GI.WebKit.Objects.EditorState as WebKit.EditorState
import {-# SOURCE #-} qualified GI.WebKit.Objects.FaviconDatabase as WebKit.FaviconDatabase
import {-# SOURCE #-} qualified GI.WebKit.Objects.FileChooserRequest as WebKit.FileChooserRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.FindController as WebKit.FindController
import {-# SOURCE #-} qualified GI.WebKit.Objects.FormSubmissionRequest as WebKit.FormSubmissionRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.GeolocationManager as WebKit.GeolocationManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.HitTestResult as WebKit.HitTestResult
import {-# SOURCE #-} qualified GI.WebKit.Objects.InputMethodContext as WebKit.InputMethodContext
import {-# SOURCE #-} qualified GI.WebKit.Objects.Notification as WebKit.Notification
import {-# SOURCE #-} qualified GI.WebKit.Objects.OptionMenu as WebKit.OptionMenu
import {-# SOURCE #-} qualified GI.WebKit.Objects.PolicyDecision as WebKit.PolicyDecision
import {-# SOURCE #-} qualified GI.WebKit.Objects.PrintOperation as WebKit.PrintOperation
import {-# SOURCE #-} qualified GI.WebKit.Objects.SecurityManager as WebKit.SecurityManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.Settings as WebKit.Settings
import {-# SOURCE #-} qualified GI.WebKit.Objects.URIRequest as WebKit.URIRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.URIResponse as WebKit.URIResponse
import {-# SOURCE #-} qualified GI.WebKit.Objects.UserContentManager as WebKit.UserContentManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.UserMessage as WebKit.UserMessage
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebContext as WebKit.WebContext
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebInspector as WebKit.WebInspector
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebResource as WebKit.WebResource
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebView as WebKit.WebView
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebViewBase as WebKit.WebViewBase
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebsiteDataManager as WebKit.WebsiteDataManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebsitePolicies as WebKit.WebsitePolicies
import {-# SOURCE #-} qualified GI.WebKit.Objects.WindowProperties as WebKit.WindowProperties
import {-# SOURCE #-} qualified GI.WebKit.Structs.ApplicationInfo as WebKit.ApplicationInfo
import {-# SOURCE #-} qualified GI.WebKit.Structs.Credential as WebKit.Credential
import {-# SOURCE #-} qualified GI.WebKit.Structs.Feature as WebKit.Feature
import {-# SOURCE #-} qualified GI.WebKit.Structs.FeatureList as WebKit.FeatureList
import {-# SOURCE #-} qualified GI.WebKit.Structs.GeolocationPosition as WebKit.GeolocationPosition
import {-# SOURCE #-} qualified GI.WebKit.Structs.ITPFirstParty as WebKit.ITPFirstParty
import {-# SOURCE #-} qualified GI.WebKit.Structs.ITPThirdParty as WebKit.ITPThirdParty
import {-# SOURCE #-} qualified GI.WebKit.Structs.InputMethodUnderline as WebKit.InputMethodUnderline
import {-# SOURCE #-} qualified GI.WebKit.Structs.MemoryPressureSettings as WebKit.MemoryPressureSettings
import {-# SOURCE #-} qualified GI.WebKit.Structs.NavigationAction as WebKit.NavigationAction
import {-# SOURCE #-} qualified GI.WebKit.Structs.NetworkProxySettings as WebKit.NetworkProxySettings
import {-# SOURCE #-} qualified GI.WebKit.Structs.OptionMenuItem as WebKit.OptionMenuItem
import {-# SOURCE #-} qualified GI.WebKit.Structs.PermissionStateQuery as WebKit.PermissionStateQuery
import {-# SOURCE #-} qualified GI.WebKit.Structs.ScriptDialog as WebKit.ScriptDialog
import {-# SOURCE #-} qualified GI.WebKit.Structs.ScriptMessageReply as WebKit.ScriptMessageReply
import {-# SOURCE #-} qualified GI.WebKit.Structs.SecurityOrigin as WebKit.SecurityOrigin
import {-# SOURCE #-} qualified GI.WebKit.Structs.UserContentFilter as WebKit.UserContentFilter
import {-# SOURCE #-} qualified GI.WebKit.Structs.UserScript as WebKit.UserScript
import {-# SOURCE #-} qualified GI.WebKit.Structs.UserStyleSheet as WebKit.UserStyleSheet
import {-# SOURCE #-} qualified GI.WebKit.Structs.WebViewSessionState as WebKit.WebViewSessionState
import {-# SOURCE #-} qualified GI.WebKit.Structs.WebsiteData as WebKit.WebsiteData
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.TlsCertificate as Gio.TlsCertificate
import {-# SOURCE #-} qualified GI.WebKit.Enums as WebKit.Enums
import {-# SOURCE #-} qualified GI.WebKit.Objects.CookieManager as WebKit.CookieManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.Download as WebKit.Download
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebsiteDataManager as WebKit.WebsiteDataManager
import {-# SOURCE #-} qualified GI.WebKit.Structs.ITPThirdParty as WebKit.ITPThirdParty
import {-# SOURCE #-} qualified GI.WebKit.Structs.MemoryPressureSettings as WebKit.MemoryPressureSettings
import {-# SOURCE #-} qualified GI.WebKit.Structs.NetworkProxySettings as WebKit.NetworkProxySettings
#endif
newtype NetworkSession = NetworkSession (SP.ManagedPtr NetworkSession)
deriving (NetworkSession -> NetworkSession -> Bool
(NetworkSession -> NetworkSession -> Bool)
-> (NetworkSession -> NetworkSession -> Bool) -> Eq NetworkSession
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NetworkSession -> NetworkSession -> Bool
== :: NetworkSession -> NetworkSession -> Bool
$c/= :: NetworkSession -> NetworkSession -> Bool
/= :: NetworkSession -> NetworkSession -> Bool
Eq)
instance SP.ManagedPtrNewtype NetworkSession where
toManagedPtr :: NetworkSession -> ManagedPtr NetworkSession
toManagedPtr (NetworkSession ManagedPtr NetworkSession
p) = ManagedPtr NetworkSession
p
foreign import ccall "webkit_network_session_get_type"
c_webkit_network_session_get_type :: IO B.Types.GType
instance B.Types.TypedObject NetworkSession where
glibType :: IO GType
glibType = IO GType
c_webkit_network_session_get_type
instance B.Types.GObject NetworkSession
class (SP.GObject o, O.IsDescendantOf NetworkSession o) => IsNetworkSession o
instance (SP.GObject o, O.IsDescendantOf NetworkSession o) => IsNetworkSession o
instance O.HasParentTypes NetworkSession
type instance O.ParentTypes NetworkSession = '[GObject.Object.Object]
toNetworkSession :: (MIO.MonadIO m, IsNetworkSession o) => o -> m NetworkSession
toNetworkSession :: forall (m :: * -> *) o.
(MonadIO m, IsNetworkSession o) =>
o -> m NetworkSession
toNetworkSession = IO NetworkSession -> m NetworkSession
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO NetworkSession -> m NetworkSession)
-> (o -> IO NetworkSession) -> o -> m NetworkSession
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr NetworkSession -> NetworkSession)
-> o -> IO NetworkSession
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr NetworkSession -> NetworkSession
NetworkSession
instance B.GValue.IsGValue (Maybe NetworkSession) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_network_session_get_type
gvalueSet_ :: Ptr GValue -> Maybe NetworkSession -> IO ()
gvalueSet_ Ptr GValue
gv Maybe NetworkSession
P.Nothing = Ptr GValue -> Ptr NetworkSession -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr NetworkSession
forall a. Ptr a
FP.nullPtr :: FP.Ptr NetworkSession)
gvalueSet_ Ptr GValue
gv (P.Just NetworkSession
obj) = NetworkSession -> (Ptr NetworkSession -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr NetworkSession
obj (Ptr GValue -> Ptr NetworkSession -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe NetworkSession)
gvalueGet_ Ptr GValue
gv = do
Ptr NetworkSession
ptr <- Ptr GValue -> IO (Ptr NetworkSession)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr NetworkSession)
if Ptr NetworkSession
ptr Ptr NetworkSession -> Ptr NetworkSession -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr NetworkSession
forall a. Ptr a
FP.nullPtr
then NetworkSession -> Maybe NetworkSession
forall a. a -> Maybe a
P.Just (NetworkSession -> Maybe NetworkSession)
-> IO NetworkSession -> IO (Maybe NetworkSession)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr NetworkSession -> NetworkSession)
-> Ptr NetworkSession -> IO NetworkSession
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr NetworkSession -> NetworkSession
NetworkSession Ptr NetworkSession
ptr
else Maybe NetworkSession -> IO (Maybe NetworkSession)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NetworkSession
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveNetworkSessionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveNetworkSessionMethod "allowTlsCertificateForHost" o = NetworkSessionAllowTlsCertificateForHostMethodInfo
ResolveNetworkSessionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveNetworkSessionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveNetworkSessionMethod "downloadUri" o = NetworkSessionDownloadUriMethodInfo
ResolveNetworkSessionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveNetworkSessionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveNetworkSessionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveNetworkSessionMethod "isEphemeral" o = NetworkSessionIsEphemeralMethodInfo
ResolveNetworkSessionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveNetworkSessionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveNetworkSessionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveNetworkSessionMethod "prefetchDns" o = NetworkSessionPrefetchDnsMethodInfo
ResolveNetworkSessionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveNetworkSessionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveNetworkSessionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveNetworkSessionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveNetworkSessionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveNetworkSessionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveNetworkSessionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveNetworkSessionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveNetworkSessionMethod "getCookieManager" o = NetworkSessionGetCookieManagerMethodInfo
ResolveNetworkSessionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveNetworkSessionMethod "getItpEnabled" o = NetworkSessionGetItpEnabledMethodInfo
ResolveNetworkSessionMethod "getItpSummary" o = NetworkSessionGetItpSummaryMethodInfo
ResolveNetworkSessionMethod "getItpSummaryFinish" o = NetworkSessionGetItpSummaryFinishMethodInfo
ResolveNetworkSessionMethod "getPersistentCredentialStorageEnabled" o = NetworkSessionGetPersistentCredentialStorageEnabledMethodInfo
ResolveNetworkSessionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveNetworkSessionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveNetworkSessionMethod "getTlsErrorsPolicy" o = NetworkSessionGetTlsErrorsPolicyMethodInfo
ResolveNetworkSessionMethod "getWebsiteDataManager" o = NetworkSessionGetWebsiteDataManagerMethodInfo
ResolveNetworkSessionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveNetworkSessionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveNetworkSessionMethod "setItpEnabled" o = NetworkSessionSetItpEnabledMethodInfo
ResolveNetworkSessionMethod "setPersistentCredentialStorageEnabled" o = NetworkSessionSetPersistentCredentialStorageEnabledMethodInfo
ResolveNetworkSessionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveNetworkSessionMethod "setProxySettings" o = NetworkSessionSetProxySettingsMethodInfo
ResolveNetworkSessionMethod "setTlsErrorsPolicy" o = NetworkSessionSetTlsErrorsPolicyMethodInfo
ResolveNetworkSessionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveNetworkSessionMethod t NetworkSession, O.OverloadedMethod info NetworkSession p) => OL.IsLabel t (NetworkSession -> 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 ~ ResolveNetworkSessionMethod t NetworkSession, O.OverloadedMethod info NetworkSession p, R.HasField t NetworkSession p) => R.HasField t NetworkSession p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveNetworkSessionMethod t NetworkSession, O.OverloadedMethodInfo info NetworkSession) => OL.IsLabel t (O.MethodProxy info NetworkSession) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type NetworkSessionDownloadStartedCallback =
WebKit.Download.Download
-> IO ()
type C_NetworkSessionDownloadStartedCallback =
Ptr NetworkSession ->
Ptr WebKit.Download.Download ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_NetworkSessionDownloadStartedCallback :: C_NetworkSessionDownloadStartedCallback -> IO (FunPtr C_NetworkSessionDownloadStartedCallback)
wrap_NetworkSessionDownloadStartedCallback ::
GObject a => (a -> NetworkSessionDownloadStartedCallback) ->
C_NetworkSessionDownloadStartedCallback
wrap_NetworkSessionDownloadStartedCallback :: forall a.
GObject a =>
(a -> NetworkSessionDownloadStartedCallback)
-> C_NetworkSessionDownloadStartedCallback
wrap_NetworkSessionDownloadStartedCallback a -> NetworkSessionDownloadStartedCallback
gi'cb Ptr NetworkSession
gi'selfPtr Ptr Download
download Ptr ()
_ = do
Download
download' <- ((ManagedPtr Download -> Download) -> Ptr Download -> IO Download
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Download -> Download
WebKit.Download.Download) Ptr Download
download
Ptr NetworkSession -> (NetworkSession -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr NetworkSession
gi'selfPtr ((NetworkSession -> IO ()) -> IO ())
-> (NetworkSession -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \NetworkSession
gi'self -> a -> NetworkSessionDownloadStartedCallback
gi'cb (NetworkSession -> a
forall a b. Coercible a b => a -> b
Coerce.coerce NetworkSession
gi'self) Download
download'
onNetworkSessionDownloadStarted :: (IsNetworkSession a, MonadIO m) => a -> ((?self :: a) => NetworkSessionDownloadStartedCallback) -> m SignalHandlerId
onNetworkSessionDownloadStarted :: forall a (m :: * -> *).
(IsNetworkSession a, MonadIO m) =>
a
-> ((?self::a) => NetworkSessionDownloadStartedCallback)
-> m SignalHandlerId
onNetworkSessionDownloadStarted a
obj (?self::a) => NetworkSessionDownloadStartedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> NetworkSessionDownloadStartedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => NetworkSessionDownloadStartedCallback
NetworkSessionDownloadStartedCallback
cb
let wrapped' :: C_NetworkSessionDownloadStartedCallback
wrapped' = (a -> NetworkSessionDownloadStartedCallback)
-> C_NetworkSessionDownloadStartedCallback
forall a.
GObject a =>
(a -> NetworkSessionDownloadStartedCallback)
-> C_NetworkSessionDownloadStartedCallback
wrap_NetworkSessionDownloadStartedCallback a -> NetworkSessionDownloadStartedCallback
wrapped
FunPtr C_NetworkSessionDownloadStartedCallback
wrapped'' <- C_NetworkSessionDownloadStartedCallback
-> IO (FunPtr C_NetworkSessionDownloadStartedCallback)
mk_NetworkSessionDownloadStartedCallback C_NetworkSessionDownloadStartedCallback
wrapped'
a
-> Text
-> FunPtr C_NetworkSessionDownloadStartedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"download-started" FunPtr C_NetworkSessionDownloadStartedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterNetworkSessionDownloadStarted :: (IsNetworkSession a, MonadIO m) => a -> ((?self :: a) => NetworkSessionDownloadStartedCallback) -> m SignalHandlerId
afterNetworkSessionDownloadStarted :: forall a (m :: * -> *).
(IsNetworkSession a, MonadIO m) =>
a
-> ((?self::a) => NetworkSessionDownloadStartedCallback)
-> m SignalHandlerId
afterNetworkSessionDownloadStarted a
obj (?self::a) => NetworkSessionDownloadStartedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> NetworkSessionDownloadStartedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => NetworkSessionDownloadStartedCallback
NetworkSessionDownloadStartedCallback
cb
let wrapped' :: C_NetworkSessionDownloadStartedCallback
wrapped' = (a -> NetworkSessionDownloadStartedCallback)
-> C_NetworkSessionDownloadStartedCallback
forall a.
GObject a =>
(a -> NetworkSessionDownloadStartedCallback)
-> C_NetworkSessionDownloadStartedCallback
wrap_NetworkSessionDownloadStartedCallback a -> NetworkSessionDownloadStartedCallback
wrapped
FunPtr C_NetworkSessionDownloadStartedCallback
wrapped'' <- C_NetworkSessionDownloadStartedCallback
-> IO (FunPtr C_NetworkSessionDownloadStartedCallback)
mk_NetworkSessionDownloadStartedCallback C_NetworkSessionDownloadStartedCallback
wrapped'
a
-> Text
-> FunPtr C_NetworkSessionDownloadStartedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"download-started" FunPtr C_NetworkSessionDownloadStartedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data NetworkSessionDownloadStartedSignalInfo
instance SignalInfo NetworkSessionDownloadStartedSignalInfo where
type HaskellCallbackType NetworkSessionDownloadStartedSignalInfo = NetworkSessionDownloadStartedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_NetworkSessionDownloadStartedCallback cb
cb'' <- mk_NetworkSessionDownloadStartedCallback cb'
connectSignalFunPtr obj "download-started" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession::download-started"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#g:signal:downloadStarted"})
#endif
constructNetworkSessionCacheDirectory :: (IsNetworkSession o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNetworkSessionCacheDirectory :: forall o (m :: * -> *).
(IsNetworkSession o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructNetworkSessionCacheDirectory Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"cache-directory" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data NetworkSessionCacheDirectoryPropertyInfo
instance AttrInfo NetworkSessionCacheDirectoryPropertyInfo where
type AttrAllowedOps NetworkSessionCacheDirectoryPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint NetworkSessionCacheDirectoryPropertyInfo = IsNetworkSession
type AttrSetTypeConstraint NetworkSessionCacheDirectoryPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint NetworkSessionCacheDirectoryPropertyInfo = (~) T.Text
type AttrTransferType NetworkSessionCacheDirectoryPropertyInfo = T.Text
type AttrGetType NetworkSessionCacheDirectoryPropertyInfo = ()
type AttrLabel NetworkSessionCacheDirectoryPropertyInfo = "cache-directory"
type AttrOrigin NetworkSessionCacheDirectoryPropertyInfo = NetworkSession
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructNetworkSessionCacheDirectory
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.cacheDirectory"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#g:attr:cacheDirectory"
})
#endif
constructNetworkSessionDataDirectory :: (IsNetworkSession o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNetworkSessionDataDirectory :: forall o (m :: * -> *).
(IsNetworkSession o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructNetworkSessionDataDirectory Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"data-directory" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data NetworkSessionDataDirectoryPropertyInfo
instance AttrInfo NetworkSessionDataDirectoryPropertyInfo where
type AttrAllowedOps NetworkSessionDataDirectoryPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint NetworkSessionDataDirectoryPropertyInfo = IsNetworkSession
type AttrSetTypeConstraint NetworkSessionDataDirectoryPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint NetworkSessionDataDirectoryPropertyInfo = (~) T.Text
type AttrTransferType NetworkSessionDataDirectoryPropertyInfo = T.Text
type AttrGetType NetworkSessionDataDirectoryPropertyInfo = ()
type AttrLabel NetworkSessionDataDirectoryPropertyInfo = "data-directory"
type AttrOrigin NetworkSessionDataDirectoryPropertyInfo = NetworkSession
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructNetworkSessionDataDirectory
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.dataDirectory"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#g:attr:dataDirectory"
})
#endif
getNetworkSessionIsEphemeral :: (MonadIO m, IsNetworkSession o) => o -> m Bool
getNetworkSessionIsEphemeral :: forall (m :: * -> *) o.
(MonadIO m, IsNetworkSession o) =>
o -> m Bool
getNetworkSessionIsEphemeral o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"is-ephemeral"
constructNetworkSessionIsEphemeral :: (IsNetworkSession o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructNetworkSessionIsEphemeral :: forall o (m :: * -> *).
(IsNetworkSession o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructNetworkSessionIsEphemeral Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"is-ephemeral" Bool
val
#if defined(ENABLE_OVERLOADING)
data NetworkSessionIsEphemeralPropertyInfo
instance AttrInfo NetworkSessionIsEphemeralPropertyInfo where
type AttrAllowedOps NetworkSessionIsEphemeralPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint NetworkSessionIsEphemeralPropertyInfo = IsNetworkSession
type AttrSetTypeConstraint NetworkSessionIsEphemeralPropertyInfo = (~) Bool
type AttrTransferTypeConstraint NetworkSessionIsEphemeralPropertyInfo = (~) Bool
type AttrTransferType NetworkSessionIsEphemeralPropertyInfo = Bool
type AttrGetType NetworkSessionIsEphemeralPropertyInfo = Bool
type AttrLabel NetworkSessionIsEphemeralPropertyInfo = "is-ephemeral"
type AttrOrigin NetworkSessionIsEphemeralPropertyInfo = NetworkSession
attrGet = getNetworkSessionIsEphemeral
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructNetworkSessionIsEphemeral
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.isEphemeral"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#g:attr:isEphemeral"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList NetworkSession
type instance O.AttributeList NetworkSession = NetworkSessionAttributeList
type NetworkSessionAttributeList = ('[ '("cacheDirectory", NetworkSessionCacheDirectoryPropertyInfo), '("dataDirectory", NetworkSessionDataDirectoryPropertyInfo), '("isEphemeral", NetworkSessionIsEphemeralPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
networkSessionCacheDirectory :: AttrLabelProxy "cacheDirectory"
networkSessionCacheDirectory = AttrLabelProxy
networkSessionDataDirectory :: AttrLabelProxy "dataDirectory"
networkSessionDataDirectory = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList NetworkSession = NetworkSessionSignalList
type NetworkSessionSignalList = ('[ '("downloadStarted", NetworkSessionDownloadStartedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "webkit_network_session_new" webkit_network_session_new ::
CString ->
CString ->
IO (Ptr NetworkSession)
networkSessionNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe (T.Text)
-> Maybe (T.Text)
-> m NetworkSession
networkSessionNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> Maybe Text -> m NetworkSession
networkSessionNew Maybe Text
dataDirectory Maybe Text
cacheDirectory = IO NetworkSession -> m NetworkSession
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkSession -> m NetworkSession)
-> IO NetworkSession -> m NetworkSession
forall a b. (a -> b) -> a -> b
$ do
Ptr CChar
maybeDataDirectory <- case Maybe Text
dataDirectory of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jDataDirectory -> do
Ptr CChar
jDataDirectory' <- Text -> IO (Ptr CChar)
textToCString Text
jDataDirectory
Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jDataDirectory'
Ptr CChar
maybeCacheDirectory <- case Maybe Text
cacheDirectory of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jCacheDirectory -> do
Ptr CChar
jCacheDirectory' <- Text -> IO (Ptr CChar)
textToCString Text
jCacheDirectory
Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jCacheDirectory'
Ptr NetworkSession
result <- Ptr CChar -> Ptr CChar -> IO (Ptr NetworkSession)
webkit_network_session_new Ptr CChar
maybeDataDirectory Ptr CChar
maybeCacheDirectory
Text -> Ptr NetworkSession -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkSessionNew" Ptr NetworkSession
result
NetworkSession
result' <- ((ManagedPtr NetworkSession -> NetworkSession)
-> Ptr NetworkSession -> IO NetworkSession
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr NetworkSession -> NetworkSession
NetworkSession) Ptr NetworkSession
result
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeDataDirectory
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeCacheDirectory
NetworkSession -> IO NetworkSession
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkSession
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "webkit_network_session_new_ephemeral" webkit_network_session_new_ephemeral ::
IO (Ptr NetworkSession)
networkSessionNewEphemeral ::
(B.CallStack.HasCallStack, MonadIO m) =>
m NetworkSession
networkSessionNewEphemeral :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m NetworkSession
networkSessionNewEphemeral = IO NetworkSession -> m NetworkSession
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkSession -> m NetworkSession)
-> IO NetworkSession -> m NetworkSession
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
result <- IO (Ptr NetworkSession)
webkit_network_session_new_ephemeral
Text -> Ptr NetworkSession -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkSessionNewEphemeral" Ptr NetworkSession
result
NetworkSession
result' <- ((ManagedPtr NetworkSession -> NetworkSession)
-> Ptr NetworkSession -> IO NetworkSession
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr NetworkSession -> NetworkSession
NetworkSession) Ptr NetworkSession
result
NetworkSession -> IO NetworkSession
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkSession
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "webkit_network_session_allow_tls_certificate_for_host" webkit_network_session_allow_tls_certificate_for_host ::
Ptr NetworkSession ->
Ptr Gio.TlsCertificate.TlsCertificate ->
CString ->
IO ()
networkSessionAllowTlsCertificateForHost ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a, Gio.TlsCertificate.IsTlsCertificate b) =>
a
-> b
-> T.Text
-> m ()
networkSessionAllowTlsCertificateForHost :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsNetworkSession a,
IsTlsCertificate b) =>
a -> b -> Text -> m ()
networkSessionAllowTlsCertificateForHost a
session b
certificate Text
host = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
Ptr TlsCertificate
certificate' <- b -> IO (Ptr TlsCertificate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
certificate
Ptr CChar
host' <- Text -> IO (Ptr CChar)
textToCString Text
host
Ptr NetworkSession -> Ptr TlsCertificate -> Ptr CChar -> IO ()
webkit_network_session_allow_tls_certificate_for_host Ptr NetworkSession
session' Ptr TlsCertificate
certificate' Ptr CChar
host'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
certificate
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
host'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkSessionAllowTlsCertificateForHostMethodInfo
instance (signature ~ (b -> T.Text -> m ()), MonadIO m, IsNetworkSession a, Gio.TlsCertificate.IsTlsCertificate b) => O.OverloadedMethod NetworkSessionAllowTlsCertificateForHostMethodInfo a signature where
overloadedMethod = networkSessionAllowTlsCertificateForHost
instance O.OverloadedMethodInfo NetworkSessionAllowTlsCertificateForHostMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionAllowTlsCertificateForHost",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionAllowTlsCertificateForHost"
})
#endif
foreign import ccall "webkit_network_session_download_uri" webkit_network_session_download_uri ::
Ptr NetworkSession ->
CString ->
IO (Ptr WebKit.Download.Download)
networkSessionDownloadUri ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> T.Text
-> m WebKit.Download.Download
networkSessionDownloadUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> Text -> m Download
networkSessionDownloadUri a
session Text
uri = IO Download -> m Download
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Download -> m Download) -> IO Download -> m Download
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
Ptr CChar
uri' <- Text -> IO (Ptr CChar)
textToCString Text
uri
Ptr Download
result <- Ptr NetworkSession -> Ptr CChar -> IO (Ptr Download)
webkit_network_session_download_uri Ptr NetworkSession
session' Ptr CChar
uri'
Text -> Ptr Download -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkSessionDownloadUri" Ptr Download
result
Download
result' <- ((ManagedPtr Download -> Download) -> Ptr Download -> IO Download
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Download -> Download
WebKit.Download.Download) Ptr Download
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
uri'
Download -> IO Download
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Download
result'
#if defined(ENABLE_OVERLOADING)
data NetworkSessionDownloadUriMethodInfo
instance (signature ~ (T.Text -> m WebKit.Download.Download), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionDownloadUriMethodInfo a signature where
overloadedMethod = networkSessionDownloadUri
instance O.OverloadedMethodInfo NetworkSessionDownloadUriMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionDownloadUri",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionDownloadUri"
})
#endif
foreign import ccall "webkit_network_session_get_cookie_manager" webkit_network_session_get_cookie_manager ::
Ptr NetworkSession ->
IO (Ptr WebKit.CookieManager.CookieManager)
networkSessionGetCookieManager ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> m WebKit.CookieManager.CookieManager
networkSessionGetCookieManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> m CookieManager
networkSessionGetCookieManager a
session = IO CookieManager -> m CookieManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CookieManager -> m CookieManager)
-> IO CookieManager -> m CookieManager
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
Ptr CookieManager
result <- Ptr NetworkSession -> IO (Ptr CookieManager)
webkit_network_session_get_cookie_manager Ptr NetworkSession
session'
Text -> Ptr CookieManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkSessionGetCookieManager" Ptr CookieManager
result
CookieManager
result' <- ((ManagedPtr CookieManager -> CookieManager)
-> Ptr CookieManager -> IO CookieManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CookieManager -> CookieManager
WebKit.CookieManager.CookieManager) Ptr CookieManager
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
CookieManager -> IO CookieManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CookieManager
result'
#if defined(ENABLE_OVERLOADING)
data NetworkSessionGetCookieManagerMethodInfo
instance (signature ~ (m WebKit.CookieManager.CookieManager), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionGetCookieManagerMethodInfo a signature where
overloadedMethod = networkSessionGetCookieManager
instance O.OverloadedMethodInfo NetworkSessionGetCookieManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionGetCookieManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionGetCookieManager"
})
#endif
foreign import ccall "webkit_network_session_get_itp_enabled" webkit_network_session_get_itp_enabled ::
Ptr NetworkSession ->
IO CInt
networkSessionGetItpEnabled ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> m Bool
networkSessionGetItpEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> m Bool
networkSessionGetItpEnabled a
session = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
CInt
result <- Ptr NetworkSession -> IO CInt
webkit_network_session_get_itp_enabled Ptr NetworkSession
session'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data NetworkSessionGetItpEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionGetItpEnabledMethodInfo a signature where
overloadedMethod = networkSessionGetItpEnabled
instance O.OverloadedMethodInfo NetworkSessionGetItpEnabledMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionGetItpEnabled",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionGetItpEnabled"
})
#endif
foreign import ccall "webkit_network_session_get_itp_summary" webkit_network_session_get_itp_summary ::
Ptr NetworkSession ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
networkSessionGetItpSummary ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
networkSessionGetItpSummary :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsNetworkSession a, IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
networkSessionGetItpSummary a
session Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr NetworkSession
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
webkit_network_session_get_itp_summary Ptr NetworkSession
session' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkSessionGetItpSummaryMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsNetworkSession a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod NetworkSessionGetItpSummaryMethodInfo a signature where
overloadedMethod = networkSessionGetItpSummary
instance O.OverloadedMethodInfo NetworkSessionGetItpSummaryMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionGetItpSummary",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionGetItpSummary"
})
#endif
foreign import ccall "webkit_network_session_get_itp_summary_finish" webkit_network_session_get_itp_summary_finish ::
Ptr NetworkSession ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr (GList (Ptr WebKit.ITPThirdParty.ITPThirdParty)))
networkSessionGetItpSummaryFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m [WebKit.ITPThirdParty.ITPThirdParty]
networkSessionGetItpSummaryFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsNetworkSession a, IsAsyncResult b) =>
a -> b -> m [ITPThirdParty]
networkSessionGetItpSummaryFinish a
session b
result_ = IO [ITPThirdParty] -> m [ITPThirdParty]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ITPThirdParty] -> m [ITPThirdParty])
-> IO [ITPThirdParty] -> m [ITPThirdParty]
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO [ITPThirdParty] -> IO () -> IO [ITPThirdParty]
forall a b. IO a -> IO b -> IO a
onException (do
Ptr (GList (Ptr ITPThirdParty))
result <- (Ptr (Ptr GError) -> IO (Ptr (GList (Ptr ITPThirdParty))))
-> IO (Ptr (GList (Ptr ITPThirdParty)))
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr (GList (Ptr ITPThirdParty))))
-> IO (Ptr (GList (Ptr ITPThirdParty))))
-> (Ptr (Ptr GError) -> IO (Ptr (GList (Ptr ITPThirdParty))))
-> IO (Ptr (GList (Ptr ITPThirdParty)))
forall a b. (a -> b) -> a -> b
$ Ptr NetworkSession
-> Ptr AsyncResult
-> Ptr (Ptr GError)
-> IO (Ptr (GList (Ptr ITPThirdParty)))
webkit_network_session_get_itp_summary_finish Ptr NetworkSession
session' Ptr AsyncResult
result_'
[Ptr ITPThirdParty]
result' <- Ptr (GList (Ptr ITPThirdParty)) -> IO [Ptr ITPThirdParty]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ITPThirdParty))
result
[ITPThirdParty]
result'' <- (Ptr ITPThirdParty -> IO ITPThirdParty)
-> [Ptr ITPThirdParty] -> IO [ITPThirdParty]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr ITPThirdParty -> ITPThirdParty)
-> Ptr ITPThirdParty -> IO ITPThirdParty
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr ITPThirdParty -> ITPThirdParty
WebKit.ITPThirdParty.ITPThirdParty) [Ptr ITPThirdParty]
result'
Ptr (GList (Ptr ITPThirdParty)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr ITPThirdParty))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
[ITPThirdParty] -> IO [ITPThirdParty]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ITPThirdParty]
result''
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data NetworkSessionGetItpSummaryFinishMethodInfo
instance (signature ~ (b -> m [WebKit.ITPThirdParty.ITPThirdParty]), MonadIO m, IsNetworkSession a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod NetworkSessionGetItpSummaryFinishMethodInfo a signature where
overloadedMethod = networkSessionGetItpSummaryFinish
instance O.OverloadedMethodInfo NetworkSessionGetItpSummaryFinishMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionGetItpSummaryFinish",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionGetItpSummaryFinish"
})
#endif
foreign import ccall "webkit_network_session_get_persistent_credential_storage_enabled" webkit_network_session_get_persistent_credential_storage_enabled ::
Ptr NetworkSession ->
IO CInt
networkSessionGetPersistentCredentialStorageEnabled ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> m Bool
networkSessionGetPersistentCredentialStorageEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> m Bool
networkSessionGetPersistentCredentialStorageEnabled a
session = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
CInt
result <- Ptr NetworkSession -> IO CInt
webkit_network_session_get_persistent_credential_storage_enabled Ptr NetworkSession
session'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data NetworkSessionGetPersistentCredentialStorageEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionGetPersistentCredentialStorageEnabledMethodInfo a signature where
overloadedMethod = networkSessionGetPersistentCredentialStorageEnabled
instance O.OverloadedMethodInfo NetworkSessionGetPersistentCredentialStorageEnabledMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionGetPersistentCredentialStorageEnabled",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionGetPersistentCredentialStorageEnabled"
})
#endif
foreign import ccall "webkit_network_session_get_tls_errors_policy" webkit_network_session_get_tls_errors_policy ::
Ptr NetworkSession ->
IO CUInt
networkSessionGetTlsErrorsPolicy ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> m WebKit.Enums.TLSErrorsPolicy
networkSessionGetTlsErrorsPolicy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> m TLSErrorsPolicy
networkSessionGetTlsErrorsPolicy a
session = IO TLSErrorsPolicy -> m TLSErrorsPolicy
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TLSErrorsPolicy -> m TLSErrorsPolicy)
-> IO TLSErrorsPolicy -> m TLSErrorsPolicy
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
CUInt
result <- Ptr NetworkSession -> IO CUInt
webkit_network_session_get_tls_errors_policy Ptr NetworkSession
session'
let result' :: TLSErrorsPolicy
result' = (Int -> TLSErrorsPolicy
forall a. Enum a => Int -> a
toEnum (Int -> TLSErrorsPolicy)
-> (CUInt -> Int) -> CUInt -> TLSErrorsPolicy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
TLSErrorsPolicy -> IO TLSErrorsPolicy
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TLSErrorsPolicy
result'
#if defined(ENABLE_OVERLOADING)
data NetworkSessionGetTlsErrorsPolicyMethodInfo
instance (signature ~ (m WebKit.Enums.TLSErrorsPolicy), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionGetTlsErrorsPolicyMethodInfo a signature where
overloadedMethod = networkSessionGetTlsErrorsPolicy
instance O.OverloadedMethodInfo NetworkSessionGetTlsErrorsPolicyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionGetTlsErrorsPolicy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionGetTlsErrorsPolicy"
})
#endif
foreign import ccall "webkit_network_session_get_website_data_manager" webkit_network_session_get_website_data_manager ::
Ptr NetworkSession ->
IO (Ptr WebKit.WebsiteDataManager.WebsiteDataManager)
networkSessionGetWebsiteDataManager ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> m WebKit.WebsiteDataManager.WebsiteDataManager
networkSessionGetWebsiteDataManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> m WebsiteDataManager
networkSessionGetWebsiteDataManager a
session = IO WebsiteDataManager -> m WebsiteDataManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WebsiteDataManager -> m WebsiteDataManager)
-> IO WebsiteDataManager -> m WebsiteDataManager
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
Ptr WebsiteDataManager
result <- Ptr NetworkSession -> IO (Ptr WebsiteDataManager)
webkit_network_session_get_website_data_manager Ptr NetworkSession
session'
Text -> Ptr WebsiteDataManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkSessionGetWebsiteDataManager" Ptr WebsiteDataManager
result
WebsiteDataManager
result' <- ((ManagedPtr WebsiteDataManager -> WebsiteDataManager)
-> Ptr WebsiteDataManager -> IO WebsiteDataManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr WebsiteDataManager -> WebsiteDataManager
WebKit.WebsiteDataManager.WebsiteDataManager) Ptr WebsiteDataManager
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
WebsiteDataManager -> IO WebsiteDataManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WebsiteDataManager
result'
#if defined(ENABLE_OVERLOADING)
data NetworkSessionGetWebsiteDataManagerMethodInfo
instance (signature ~ (m WebKit.WebsiteDataManager.WebsiteDataManager), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionGetWebsiteDataManagerMethodInfo a signature where
overloadedMethod = networkSessionGetWebsiteDataManager
instance O.OverloadedMethodInfo NetworkSessionGetWebsiteDataManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionGetWebsiteDataManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionGetWebsiteDataManager"
})
#endif
foreign import ccall "webkit_network_session_is_ephemeral" webkit_network_session_is_ephemeral ::
Ptr NetworkSession ->
IO CInt
networkSessionIsEphemeral ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> m Bool
networkSessionIsEphemeral :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> m Bool
networkSessionIsEphemeral a
session = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
CInt
result <- Ptr NetworkSession -> IO CInt
webkit_network_session_is_ephemeral Ptr NetworkSession
session'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data NetworkSessionIsEphemeralMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionIsEphemeralMethodInfo a signature where
overloadedMethod = networkSessionIsEphemeral
instance O.OverloadedMethodInfo NetworkSessionIsEphemeralMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionIsEphemeral",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionIsEphemeral"
})
#endif
foreign import ccall "webkit_network_session_prefetch_dns" webkit_network_session_prefetch_dns ::
Ptr NetworkSession ->
CString ->
IO ()
networkSessionPrefetchDns ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> T.Text
-> m ()
networkSessionPrefetchDns :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> Text -> m ()
networkSessionPrefetchDns a
session Text
hostname = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
Ptr CChar
hostname' <- Text -> IO (Ptr CChar)
textToCString Text
hostname
Ptr NetworkSession -> Ptr CChar -> IO ()
webkit_network_session_prefetch_dns Ptr NetworkSession
session' Ptr CChar
hostname'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
hostname'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkSessionPrefetchDnsMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionPrefetchDnsMethodInfo a signature where
overloadedMethod = networkSessionPrefetchDns
instance O.OverloadedMethodInfo NetworkSessionPrefetchDnsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionPrefetchDns",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionPrefetchDns"
})
#endif
foreign import ccall "webkit_network_session_set_itp_enabled" webkit_network_session_set_itp_enabled ::
Ptr NetworkSession ->
CInt ->
IO ()
networkSessionSetItpEnabled ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> Bool
-> m ()
networkSessionSetItpEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> Bool -> m ()
networkSessionSetItpEnabled a
session Bool
enabled = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
let enabled' :: CInt
enabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
enabled
Ptr NetworkSession -> CInt -> IO ()
webkit_network_session_set_itp_enabled Ptr NetworkSession
session' CInt
enabled'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkSessionSetItpEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionSetItpEnabledMethodInfo a signature where
overloadedMethod = networkSessionSetItpEnabled
instance O.OverloadedMethodInfo NetworkSessionSetItpEnabledMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionSetItpEnabled",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionSetItpEnabled"
})
#endif
foreign import ccall "webkit_network_session_set_persistent_credential_storage_enabled" webkit_network_session_set_persistent_credential_storage_enabled ::
Ptr NetworkSession ->
CInt ->
IO ()
networkSessionSetPersistentCredentialStorageEnabled ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> Bool
-> m ()
networkSessionSetPersistentCredentialStorageEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> Bool -> m ()
networkSessionSetPersistentCredentialStorageEnabled a
session Bool
enabled = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
let enabled' :: CInt
enabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
enabled
Ptr NetworkSession -> CInt -> IO ()
webkit_network_session_set_persistent_credential_storage_enabled Ptr NetworkSession
session' CInt
enabled'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkSessionSetPersistentCredentialStorageEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionSetPersistentCredentialStorageEnabledMethodInfo a signature where
overloadedMethod = networkSessionSetPersistentCredentialStorageEnabled
instance O.OverloadedMethodInfo NetworkSessionSetPersistentCredentialStorageEnabledMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionSetPersistentCredentialStorageEnabled",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionSetPersistentCredentialStorageEnabled"
})
#endif
foreign import ccall "webkit_network_session_set_proxy_settings" webkit_network_session_set_proxy_settings ::
Ptr NetworkSession ->
CUInt ->
Ptr WebKit.NetworkProxySettings.NetworkProxySettings ->
IO ()
networkSessionSetProxySettings ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> WebKit.Enums.NetworkProxyMode
-> Maybe (WebKit.NetworkProxySettings.NetworkProxySettings)
-> m ()
networkSessionSetProxySettings :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> NetworkProxyMode -> Maybe NetworkProxySettings -> m ()
networkSessionSetProxySettings a
session NetworkProxyMode
proxyMode Maybe NetworkProxySettings
proxySettings = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
let proxyMode' :: CUInt
proxyMode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (NetworkProxyMode -> Int) -> NetworkProxyMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NetworkProxyMode -> Int
forall a. Enum a => a -> Int
fromEnum) NetworkProxyMode
proxyMode
Ptr NetworkProxySettings
maybeProxySettings <- case Maybe NetworkProxySettings
proxySettings of
Maybe NetworkProxySettings
Nothing -> Ptr NetworkProxySettings -> IO (Ptr NetworkProxySettings)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr NetworkProxySettings
forall a. Ptr a
nullPtr
Just NetworkProxySettings
jProxySettings -> do
Ptr NetworkProxySettings
jProxySettings' <- NetworkProxySettings -> IO (Ptr NetworkProxySettings)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr NetworkProxySettings
jProxySettings
Ptr NetworkProxySettings -> IO (Ptr NetworkProxySettings)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr NetworkProxySettings
jProxySettings'
Ptr NetworkSession -> CUInt -> Ptr NetworkProxySettings -> IO ()
webkit_network_session_set_proxy_settings Ptr NetworkSession
session' CUInt
proxyMode' Ptr NetworkProxySettings
maybeProxySettings
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
Maybe NetworkProxySettings
-> (NetworkProxySettings -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe NetworkProxySettings
proxySettings NetworkProxySettings -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkSessionSetProxySettingsMethodInfo
instance (signature ~ (WebKit.Enums.NetworkProxyMode -> Maybe (WebKit.NetworkProxySettings.NetworkProxySettings) -> m ()), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionSetProxySettingsMethodInfo a signature where
overloadedMethod = networkSessionSetProxySettings
instance O.OverloadedMethodInfo NetworkSessionSetProxySettingsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionSetProxySettings",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionSetProxySettings"
})
#endif
foreign import ccall "webkit_network_session_set_tls_errors_policy" webkit_network_session_set_tls_errors_policy ::
Ptr NetworkSession ->
CUInt ->
IO ()
networkSessionSetTlsErrorsPolicy ::
(B.CallStack.HasCallStack, MonadIO m, IsNetworkSession a) =>
a
-> WebKit.Enums.TLSErrorsPolicy
-> m ()
networkSessionSetTlsErrorsPolicy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNetworkSession a) =>
a -> TLSErrorsPolicy -> m ()
networkSessionSetTlsErrorsPolicy a
session TLSErrorsPolicy
policy = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
session' <- a -> IO (Ptr NetworkSession)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
session
let policy' :: CUInt
policy' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TLSErrorsPolicy -> Int) -> TLSErrorsPolicy -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TLSErrorsPolicy -> Int
forall a. Enum a => a -> Int
fromEnum) TLSErrorsPolicy
policy
Ptr NetworkSession -> CUInt -> IO ()
webkit_network_session_set_tls_errors_policy Ptr NetworkSession
session' CUInt
policy'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
session
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NetworkSessionSetTlsErrorsPolicyMethodInfo
instance (signature ~ (WebKit.Enums.TLSErrorsPolicy -> m ()), MonadIO m, IsNetworkSession a) => O.OverloadedMethod NetworkSessionSetTlsErrorsPolicyMethodInfo a signature where
overloadedMethod = networkSessionSetTlsErrorsPolicy
instance O.OverloadedMethodInfo NetworkSessionSetTlsErrorsPolicyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.NetworkSession.networkSessionSetTlsErrorsPolicy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-NetworkSession.html#v:networkSessionSetTlsErrorsPolicy"
})
#endif
foreign import ccall "webkit_network_session_get_default" webkit_network_session_get_default ::
IO (Ptr NetworkSession)
networkSessionGetDefault ::
(B.CallStack.HasCallStack, MonadIO m) =>
m NetworkSession
networkSessionGetDefault :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m NetworkSession
networkSessionGetDefault = IO NetworkSession -> m NetworkSession
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NetworkSession -> m NetworkSession)
-> IO NetworkSession -> m NetworkSession
forall a b. (a -> b) -> a -> b
$ do
Ptr NetworkSession
result <- IO (Ptr NetworkSession)
webkit_network_session_get_default
Text -> Ptr NetworkSession -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"networkSessionGetDefault" Ptr NetworkSession
result
NetworkSession
result' <- ((ManagedPtr NetworkSession -> NetworkSession)
-> Ptr NetworkSession -> IO NetworkSession
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr NetworkSession -> NetworkSession
NetworkSession) Ptr NetworkSession
result
NetworkSession -> IO NetworkSession
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkSession
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "webkit_network_session_set_memory_pressure_settings" webkit_network_session_set_memory_pressure_settings ::
Ptr WebKit.MemoryPressureSettings.MemoryPressureSettings ->
IO ()
networkSessionSetMemoryPressureSettings ::
(B.CallStack.HasCallStack, MonadIO m) =>
WebKit.MemoryPressureSettings.MemoryPressureSettings
-> m ()
networkSessionSetMemoryPressureSettings :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MemoryPressureSettings -> m ()
networkSessionSetMemoryPressureSettings MemoryPressureSettings
settings = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr MemoryPressureSettings
settings' <- MemoryPressureSettings -> IO (Ptr MemoryPressureSettings)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MemoryPressureSettings
settings
Ptr MemoryPressureSettings -> IO ()
webkit_network_session_set_memory_pressure_settings Ptr MemoryPressureSettings
settings'
MemoryPressureSettings -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MemoryPressureSettings
settings
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
#endif