{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.WebKit.Objects.WebContext
(
WebContext(..) ,
IsWebContext ,
toWebContext ,
#if defined(ENABLE_OVERLOADING)
ResolveWebContextMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
WebContextAddPathToSandboxMethodInfo ,
#endif
webContextAddPathToSandbox ,
#if defined(ENABLE_OVERLOADING)
WebContextGetCacheModelMethodInfo ,
#endif
webContextGetCacheModel ,
webContextGetDefault ,
#if defined(ENABLE_OVERLOADING)
WebContextGetGeolocationManagerMethodInfo,
#endif
webContextGetGeolocationManager ,
#if defined(ENABLE_OVERLOADING)
WebContextGetNetworkSessionForAutomationMethodInfo,
#endif
webContextGetNetworkSessionForAutomation,
#if defined(ENABLE_OVERLOADING)
WebContextGetSecurityManagerMethodInfo ,
#endif
webContextGetSecurityManager ,
#if defined(ENABLE_OVERLOADING)
WebContextGetSpellCheckingEnabledMethodInfo,
#endif
webContextGetSpellCheckingEnabled ,
#if defined(ENABLE_OVERLOADING)
WebContextGetSpellCheckingLanguagesMethodInfo,
#endif
webContextGetSpellCheckingLanguages ,
#if defined(ENABLE_OVERLOADING)
WebContextGetTimeZoneOverrideMethodInfo ,
#endif
webContextGetTimeZoneOverride ,
#if defined(ENABLE_OVERLOADING)
WebContextInitializeNotificationPermissionsMethodInfo,
#endif
webContextInitializeNotificationPermissions,
#if defined(ENABLE_OVERLOADING)
WebContextIsAutomationAllowedMethodInfo ,
#endif
webContextIsAutomationAllowed ,
webContextNew ,
#if defined(ENABLE_OVERLOADING)
WebContextRegisterUriSchemeMethodInfo ,
#endif
webContextRegisterUriScheme ,
#if defined(ENABLE_OVERLOADING)
WebContextSendMessageToAllExtensionsMethodInfo,
#endif
webContextSendMessageToAllExtensions ,
#if defined(ENABLE_OVERLOADING)
WebContextSetAutomationAllowedMethodInfo,
#endif
webContextSetAutomationAllowed ,
#if defined(ENABLE_OVERLOADING)
WebContextSetCacheModelMethodInfo ,
#endif
webContextSetCacheModel ,
#if defined(ENABLE_OVERLOADING)
WebContextSetPreferredLanguagesMethodInfo,
#endif
webContextSetPreferredLanguages ,
#if defined(ENABLE_OVERLOADING)
WebContextSetSpellCheckingEnabledMethodInfo,
#endif
webContextSetSpellCheckingEnabled ,
#if defined(ENABLE_OVERLOADING)
WebContextSetSpellCheckingLanguagesMethodInfo,
#endif
webContextSetSpellCheckingLanguages ,
#if defined(ENABLE_OVERLOADING)
WebContextSetWebProcessExtensionsDirectoryMethodInfo,
#endif
webContextSetWebProcessExtensionsDirectory,
#if defined(ENABLE_OVERLOADING)
WebContextSetWebProcessExtensionsInitializationUserDataMethodInfo,
#endif
webContextSetWebProcessExtensionsInitializationUserData,
#if defined(ENABLE_OVERLOADING)
WebContextMemoryPressureSettingsPropertyInfo,
#endif
constructWebContextMemoryPressureSettings,
#if defined(ENABLE_OVERLOADING)
webContextMemoryPressureSettings ,
#endif
#if defined(ENABLE_OVERLOADING)
WebContextTimeZoneOverridePropertyInfo ,
#endif
constructWebContextTimeZoneOverride ,
getWebContextTimeZoneOverride ,
#if defined(ENABLE_OVERLOADING)
webContextTimeZoneOverride ,
#endif
WebContextAutomationStartedCallback ,
#if defined(ENABLE_OVERLOADING)
WebContextAutomationStartedSignalInfo ,
#endif
afterWebContextAutomationStarted ,
onWebContextAutomationStarted ,
WebContextInitializeNotificationPermissionsCallback,
#if defined(ENABLE_OVERLOADING)
WebContextInitializeNotificationPermissionsSignalInfo,
#endif
afterWebContextInitializeNotificationPermissions,
onWebContextInitializeNotificationPermissions,
WebContextInitializeWebProcessExtensionsCallback,
#if defined(ENABLE_OVERLOADING)
WebContextInitializeWebProcessExtensionsSignalInfo,
#endif
afterWebContextInitializeWebProcessExtensions,
onWebContextInitializeWebProcessExtensions,
WebContextUserMessageReceivedCallback ,
#if defined(ENABLE_OVERLOADING)
WebContextUserMessageReceivedSignalInfo ,
#endif
afterWebContextUserMessageReceived ,
onWebContextUserMessageReceived ,
) 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.NetworkSession as WebKit.NetworkSession
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.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.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.WebKit.Callbacks as WebKit.Callbacks
import {-# SOURCE #-} qualified GI.WebKit.Enums as WebKit.Enums
import {-# SOURCE #-} qualified GI.WebKit.Objects.AutomationSession as WebKit.AutomationSession
import {-# SOURCE #-} qualified GI.WebKit.Objects.GeolocationManager as WebKit.GeolocationManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.NetworkSession as WebKit.NetworkSession
import {-# SOURCE #-} qualified GI.WebKit.Objects.SecurityManager as WebKit.SecurityManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.UserMessage as WebKit.UserMessage
import {-# SOURCE #-} qualified GI.WebKit.Structs.MemoryPressureSettings as WebKit.MemoryPressureSettings
import {-# SOURCE #-} qualified GI.WebKit.Structs.SecurityOrigin as WebKit.SecurityOrigin
#endif
newtype WebContext = WebContext (SP.ManagedPtr WebContext)
deriving (WebContext -> WebContext -> Bool
(WebContext -> WebContext -> Bool)
-> (WebContext -> WebContext -> Bool) -> Eq WebContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebContext -> WebContext -> Bool
== :: WebContext -> WebContext -> Bool
$c/= :: WebContext -> WebContext -> Bool
/= :: WebContext -> WebContext -> Bool
Eq)
instance SP.ManagedPtrNewtype WebContext where
toManagedPtr :: WebContext -> ManagedPtr WebContext
toManagedPtr (WebContext ManagedPtr WebContext
p) = ManagedPtr WebContext
p
foreign import ccall "webkit_web_context_get_type"
c_webkit_web_context_get_type :: IO B.Types.GType
instance B.Types.TypedObject WebContext where
glibType :: IO GType
glibType = IO GType
c_webkit_web_context_get_type
instance B.Types.GObject WebContext
class (SP.GObject o, O.IsDescendantOf WebContext o) => IsWebContext o
instance (SP.GObject o, O.IsDescendantOf WebContext o) => IsWebContext o
instance O.HasParentTypes WebContext
type instance O.ParentTypes WebContext = '[GObject.Object.Object]
toWebContext :: (MIO.MonadIO m, IsWebContext o) => o -> m WebContext
toWebContext :: forall (m :: * -> *) o.
(MonadIO m, IsWebContext o) =>
o -> m WebContext
toWebContext = IO WebContext -> m WebContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO WebContext -> m WebContext)
-> (o -> IO WebContext) -> o -> m WebContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr WebContext -> WebContext) -> o -> IO WebContext
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr WebContext -> WebContext
WebContext
instance B.GValue.IsGValue (Maybe WebContext) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_web_context_get_type
gvalueSet_ :: Ptr GValue -> Maybe WebContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe WebContext
P.Nothing = Ptr GValue -> Ptr WebContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr WebContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr WebContext)
gvalueSet_ Ptr GValue
gv (P.Just WebContext
obj) = WebContext -> (Ptr WebContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr WebContext
obj (Ptr GValue -> Ptr WebContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe WebContext)
gvalueGet_ Ptr GValue
gv = do
Ptr WebContext
ptr <- Ptr GValue -> IO (Ptr WebContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr WebContext)
if Ptr WebContext
ptr Ptr WebContext -> Ptr WebContext -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr WebContext
forall a. Ptr a
FP.nullPtr
then WebContext -> Maybe WebContext
forall a. a -> Maybe a
P.Just (WebContext -> Maybe WebContext)
-> IO WebContext -> IO (Maybe WebContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr WebContext -> WebContext)
-> Ptr WebContext -> IO WebContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr WebContext -> WebContext
WebContext Ptr WebContext
ptr
else Maybe WebContext -> IO (Maybe WebContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebContext
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveWebContextMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveWebContextMethod "addPathToSandbox" o = WebContextAddPathToSandboxMethodInfo
ResolveWebContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveWebContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveWebContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveWebContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveWebContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveWebContextMethod "initializeNotificationPermissions" o = WebContextInitializeNotificationPermissionsMethodInfo
ResolveWebContextMethod "isAutomationAllowed" o = WebContextIsAutomationAllowedMethodInfo
ResolveWebContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveWebContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveWebContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveWebContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveWebContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveWebContextMethod "registerUriScheme" o = WebContextRegisterUriSchemeMethodInfo
ResolveWebContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveWebContextMethod "sendMessageToAllExtensions" o = WebContextSendMessageToAllExtensionsMethodInfo
ResolveWebContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveWebContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveWebContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveWebContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveWebContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveWebContextMethod "getCacheModel" o = WebContextGetCacheModelMethodInfo
ResolveWebContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveWebContextMethod "getGeolocationManager" o = WebContextGetGeolocationManagerMethodInfo
ResolveWebContextMethod "getNetworkSessionForAutomation" o = WebContextGetNetworkSessionForAutomationMethodInfo
ResolveWebContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveWebContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveWebContextMethod "getSecurityManager" o = WebContextGetSecurityManagerMethodInfo
ResolveWebContextMethod "getSpellCheckingEnabled" o = WebContextGetSpellCheckingEnabledMethodInfo
ResolveWebContextMethod "getSpellCheckingLanguages" o = WebContextGetSpellCheckingLanguagesMethodInfo
ResolveWebContextMethod "getTimeZoneOverride" o = WebContextGetTimeZoneOverrideMethodInfo
ResolveWebContextMethod "setAutomationAllowed" o = WebContextSetAutomationAllowedMethodInfo
ResolveWebContextMethod "setCacheModel" o = WebContextSetCacheModelMethodInfo
ResolveWebContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveWebContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveWebContextMethod "setPreferredLanguages" o = WebContextSetPreferredLanguagesMethodInfo
ResolveWebContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveWebContextMethod "setSpellCheckingEnabled" o = WebContextSetSpellCheckingEnabledMethodInfo
ResolveWebContextMethod "setSpellCheckingLanguages" o = WebContextSetSpellCheckingLanguagesMethodInfo
ResolveWebContextMethod "setWebProcessExtensionsDirectory" o = WebContextSetWebProcessExtensionsDirectoryMethodInfo
ResolveWebContextMethod "setWebProcessExtensionsInitializationUserData" o = WebContextSetWebProcessExtensionsInitializationUserDataMethodInfo
ResolveWebContextMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveWebContextMethod t WebContext, O.OverloadedMethod info WebContext p) => OL.IsLabel t (WebContext -> 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 ~ ResolveWebContextMethod t WebContext, O.OverloadedMethod info WebContext p, R.HasField t WebContext p) => R.HasField t WebContext p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveWebContextMethod t WebContext, O.OverloadedMethodInfo info WebContext) => OL.IsLabel t (O.MethodProxy info WebContext) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type WebContextAutomationStartedCallback =
WebKit.AutomationSession.AutomationSession
-> IO ()
type C_WebContextAutomationStartedCallback =
Ptr WebContext ->
Ptr WebKit.AutomationSession.AutomationSession ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_WebContextAutomationStartedCallback :: C_WebContextAutomationStartedCallback -> IO (FunPtr C_WebContextAutomationStartedCallback)
wrap_WebContextAutomationStartedCallback ::
GObject a => (a -> WebContextAutomationStartedCallback) ->
C_WebContextAutomationStartedCallback
wrap_WebContextAutomationStartedCallback :: forall a.
GObject a =>
(a -> WebContextAutomationStartedCallback)
-> C_WebContextAutomationStartedCallback
wrap_WebContextAutomationStartedCallback a -> WebContextAutomationStartedCallback
gi'cb Ptr WebContext
gi'selfPtr Ptr AutomationSession
session Ptr ()
_ = do
AutomationSession
session' <- ((ManagedPtr AutomationSession -> AutomationSession)
-> Ptr AutomationSession -> IO AutomationSession
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AutomationSession -> AutomationSession
WebKit.AutomationSession.AutomationSession) Ptr AutomationSession
session
Ptr WebContext -> (WebContext -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr WebContext
gi'selfPtr ((WebContext -> IO ()) -> IO ()) -> (WebContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \WebContext
gi'self -> a -> WebContextAutomationStartedCallback
gi'cb (WebContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce WebContext
gi'self) AutomationSession
session'
onWebContextAutomationStarted :: (IsWebContext a, MonadIO m) => a -> ((?self :: a) => WebContextAutomationStartedCallback) -> m SignalHandlerId
onWebContextAutomationStarted :: forall a (m :: * -> *).
(IsWebContext a, MonadIO m) =>
a
-> ((?self::a) => WebContextAutomationStartedCallback)
-> m SignalHandlerId
onWebContextAutomationStarted a
obj (?self::a) => WebContextAutomationStartedCallback
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 -> WebContextAutomationStartedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => WebContextAutomationStartedCallback
WebContextAutomationStartedCallback
cb
let wrapped' :: C_WebContextAutomationStartedCallback
wrapped' = (a -> WebContextAutomationStartedCallback)
-> C_WebContextAutomationStartedCallback
forall a.
GObject a =>
(a -> WebContextAutomationStartedCallback)
-> C_WebContextAutomationStartedCallback
wrap_WebContextAutomationStartedCallback a -> WebContextAutomationStartedCallback
wrapped
FunPtr C_WebContextAutomationStartedCallback
wrapped'' <- C_WebContextAutomationStartedCallback
-> IO (FunPtr C_WebContextAutomationStartedCallback)
mk_WebContextAutomationStartedCallback C_WebContextAutomationStartedCallback
wrapped'
a
-> Text
-> FunPtr C_WebContextAutomationStartedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"automation-started" FunPtr C_WebContextAutomationStartedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterWebContextAutomationStarted :: (IsWebContext a, MonadIO m) => a -> ((?self :: a) => WebContextAutomationStartedCallback) -> m SignalHandlerId
afterWebContextAutomationStarted :: forall a (m :: * -> *).
(IsWebContext a, MonadIO m) =>
a
-> ((?self::a) => WebContextAutomationStartedCallback)
-> m SignalHandlerId
afterWebContextAutomationStarted a
obj (?self::a) => WebContextAutomationStartedCallback
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 -> WebContextAutomationStartedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => WebContextAutomationStartedCallback
WebContextAutomationStartedCallback
cb
let wrapped' :: C_WebContextAutomationStartedCallback
wrapped' = (a -> WebContextAutomationStartedCallback)
-> C_WebContextAutomationStartedCallback
forall a.
GObject a =>
(a -> WebContextAutomationStartedCallback)
-> C_WebContextAutomationStartedCallback
wrap_WebContextAutomationStartedCallback a -> WebContextAutomationStartedCallback
wrapped
FunPtr C_WebContextAutomationStartedCallback
wrapped'' <- C_WebContextAutomationStartedCallback
-> IO (FunPtr C_WebContextAutomationStartedCallback)
mk_WebContextAutomationStartedCallback C_WebContextAutomationStartedCallback
wrapped'
a
-> Text
-> FunPtr C_WebContextAutomationStartedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"automation-started" FunPtr C_WebContextAutomationStartedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data WebContextAutomationStartedSignalInfo
instance SignalInfo WebContextAutomationStartedSignalInfo where
type HaskellCallbackType WebContextAutomationStartedSignalInfo = WebContextAutomationStartedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_WebContextAutomationStartedCallback cb
cb'' <- mk_WebContextAutomationStartedCallback cb'
connectSignalFunPtr obj "automation-started" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext::automation-started"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#g:signal:automationStarted"})
#endif
type WebContextInitializeNotificationPermissionsCallback =
IO ()
type C_WebContextInitializeNotificationPermissionsCallback =
Ptr WebContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_WebContextInitializeNotificationPermissionsCallback :: C_WebContextInitializeNotificationPermissionsCallback -> IO (FunPtr C_WebContextInitializeNotificationPermissionsCallback)
wrap_WebContextInitializeNotificationPermissionsCallback ::
GObject a => (a -> WebContextInitializeNotificationPermissionsCallback) ->
C_WebContextInitializeNotificationPermissionsCallback
wrap_WebContextInitializeNotificationPermissionsCallback :: forall a.
GObject a =>
(a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
wrap_WebContextInitializeNotificationPermissionsCallback a -> IO ()
gi'cb Ptr WebContext
gi'selfPtr Ptr ()
_ = do
Ptr WebContext -> (WebContext -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr WebContext
gi'selfPtr ((WebContext -> IO ()) -> IO ()) -> (WebContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \WebContext
gi'self -> a -> IO ()
gi'cb (WebContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce WebContext
gi'self)
onWebContextInitializeNotificationPermissions :: (IsWebContext a, MonadIO m) => a -> ((?self :: a) => WebContextInitializeNotificationPermissionsCallback) -> m SignalHandlerId
onWebContextInitializeNotificationPermissions :: forall a (m :: * -> *).
(IsWebContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onWebContextInitializeNotificationPermissions a
obj (?self::a) => IO ()
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 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_WebContextInitializeNotificationPermissionsCallback
wrapped' = (a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
forall a.
GObject a =>
(a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
wrap_WebContextInitializeNotificationPermissionsCallback a -> IO ()
wrapped
FunPtr C_WebContextInitializeNotificationPermissionsCallback
wrapped'' <- C_WebContextInitializeNotificationPermissionsCallback
-> IO
(FunPtr C_WebContextInitializeNotificationPermissionsCallback)
mk_WebContextInitializeNotificationPermissionsCallback C_WebContextInitializeNotificationPermissionsCallback
wrapped'
a
-> Text
-> FunPtr C_WebContextInitializeNotificationPermissionsCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"initialize-notification-permissions" FunPtr C_WebContextInitializeNotificationPermissionsCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterWebContextInitializeNotificationPermissions :: (IsWebContext a, MonadIO m) => a -> ((?self :: a) => WebContextInitializeNotificationPermissionsCallback) -> m SignalHandlerId
afterWebContextInitializeNotificationPermissions :: forall a (m :: * -> *).
(IsWebContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterWebContextInitializeNotificationPermissions a
obj (?self::a) => IO ()
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 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_WebContextInitializeNotificationPermissionsCallback
wrapped' = (a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
forall a.
GObject a =>
(a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
wrap_WebContextInitializeNotificationPermissionsCallback a -> IO ()
wrapped
FunPtr C_WebContextInitializeNotificationPermissionsCallback
wrapped'' <- C_WebContextInitializeNotificationPermissionsCallback
-> IO
(FunPtr C_WebContextInitializeNotificationPermissionsCallback)
mk_WebContextInitializeNotificationPermissionsCallback C_WebContextInitializeNotificationPermissionsCallback
wrapped'
a
-> Text
-> FunPtr C_WebContextInitializeNotificationPermissionsCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"initialize-notification-permissions" FunPtr C_WebContextInitializeNotificationPermissionsCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data WebContextInitializeNotificationPermissionsSignalInfo
instance SignalInfo WebContextInitializeNotificationPermissionsSignalInfo where
type HaskellCallbackType WebContextInitializeNotificationPermissionsSignalInfo = WebContextInitializeNotificationPermissionsCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_WebContextInitializeNotificationPermissionsCallback cb
cb'' <- mk_WebContextInitializeNotificationPermissionsCallback cb'
connectSignalFunPtr obj "initialize-notification-permissions" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext::initialize-notification-permissions"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#g:signal:initializeNotificationPermissions"})
#endif
type WebContextInitializeWebProcessExtensionsCallback =
IO ()
type C_WebContextInitializeWebProcessExtensionsCallback =
Ptr WebContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_WebContextInitializeWebProcessExtensionsCallback :: C_WebContextInitializeWebProcessExtensionsCallback -> IO (FunPtr C_WebContextInitializeWebProcessExtensionsCallback)
wrap_WebContextInitializeWebProcessExtensionsCallback ::
GObject a => (a -> WebContextInitializeWebProcessExtensionsCallback) ->
C_WebContextInitializeWebProcessExtensionsCallback
wrap_WebContextInitializeWebProcessExtensionsCallback :: forall a.
GObject a =>
(a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
wrap_WebContextInitializeWebProcessExtensionsCallback a -> IO ()
gi'cb Ptr WebContext
gi'selfPtr Ptr ()
_ = do
Ptr WebContext -> (WebContext -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr WebContext
gi'selfPtr ((WebContext -> IO ()) -> IO ()) -> (WebContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \WebContext
gi'self -> a -> IO ()
gi'cb (WebContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce WebContext
gi'self)
onWebContextInitializeWebProcessExtensions :: (IsWebContext a, MonadIO m) => a -> ((?self :: a) => WebContextInitializeWebProcessExtensionsCallback) -> m SignalHandlerId
onWebContextInitializeWebProcessExtensions :: forall a (m :: * -> *).
(IsWebContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onWebContextInitializeWebProcessExtensions a
obj (?self::a) => IO ()
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 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_WebContextInitializeNotificationPermissionsCallback
wrapped' = (a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
forall a.
GObject a =>
(a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
wrap_WebContextInitializeWebProcessExtensionsCallback a -> IO ()
wrapped
FunPtr C_WebContextInitializeNotificationPermissionsCallback
wrapped'' <- C_WebContextInitializeNotificationPermissionsCallback
-> IO
(FunPtr C_WebContextInitializeNotificationPermissionsCallback)
mk_WebContextInitializeWebProcessExtensionsCallback C_WebContextInitializeNotificationPermissionsCallback
wrapped'
a
-> Text
-> FunPtr C_WebContextInitializeNotificationPermissionsCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"initialize-web-process-extensions" FunPtr C_WebContextInitializeNotificationPermissionsCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterWebContextInitializeWebProcessExtensions :: (IsWebContext a, MonadIO m) => a -> ((?self :: a) => WebContextInitializeWebProcessExtensionsCallback) -> m SignalHandlerId
afterWebContextInitializeWebProcessExtensions :: forall a (m :: * -> *).
(IsWebContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterWebContextInitializeWebProcessExtensions a
obj (?self::a) => IO ()
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 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_WebContextInitializeNotificationPermissionsCallback
wrapped' = (a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
forall a.
GObject a =>
(a -> IO ())
-> C_WebContextInitializeNotificationPermissionsCallback
wrap_WebContextInitializeWebProcessExtensionsCallback a -> IO ()
wrapped
FunPtr C_WebContextInitializeNotificationPermissionsCallback
wrapped'' <- C_WebContextInitializeNotificationPermissionsCallback
-> IO
(FunPtr C_WebContextInitializeNotificationPermissionsCallback)
mk_WebContextInitializeWebProcessExtensionsCallback C_WebContextInitializeNotificationPermissionsCallback
wrapped'
a
-> Text
-> FunPtr C_WebContextInitializeNotificationPermissionsCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"initialize-web-process-extensions" FunPtr C_WebContextInitializeNotificationPermissionsCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data WebContextInitializeWebProcessExtensionsSignalInfo
instance SignalInfo WebContextInitializeWebProcessExtensionsSignalInfo where
type HaskellCallbackType WebContextInitializeWebProcessExtensionsSignalInfo = WebContextInitializeWebProcessExtensionsCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_WebContextInitializeWebProcessExtensionsCallback cb
cb'' <- mk_WebContextInitializeWebProcessExtensionsCallback cb'
connectSignalFunPtr obj "initialize-web-process-extensions" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext::initialize-web-process-extensions"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#g:signal:initializeWebProcessExtensions"})
#endif
type WebContextUserMessageReceivedCallback =
WebKit.UserMessage.UserMessage
-> IO Bool
type C_WebContextUserMessageReceivedCallback =
Ptr WebContext ->
Ptr WebKit.UserMessage.UserMessage ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_WebContextUserMessageReceivedCallback :: C_WebContextUserMessageReceivedCallback -> IO (FunPtr C_WebContextUserMessageReceivedCallback)
wrap_WebContextUserMessageReceivedCallback ::
GObject a => (a -> WebContextUserMessageReceivedCallback) ->
C_WebContextUserMessageReceivedCallback
wrap_WebContextUserMessageReceivedCallback :: forall a.
GObject a =>
(a -> WebContextUserMessageReceivedCallback)
-> C_WebContextUserMessageReceivedCallback
wrap_WebContextUserMessageReceivedCallback a -> WebContextUserMessageReceivedCallback
gi'cb Ptr WebContext
gi'selfPtr Ptr UserMessage
message Ptr ()
_ = do
UserMessage
message' <- ((ManagedPtr UserMessage -> UserMessage)
-> Ptr UserMessage -> IO UserMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr UserMessage -> UserMessage
WebKit.UserMessage.UserMessage) Ptr UserMessage
message
Bool
result <- Ptr WebContext -> (WebContext -> IO Bool) -> IO Bool
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr WebContext
gi'selfPtr ((WebContext -> IO Bool) -> IO Bool)
-> (WebContext -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \WebContext
gi'self -> a -> WebContextUserMessageReceivedCallback
gi'cb (WebContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce WebContext
gi'self) UserMessage
message'
let result' :: CInt
result' = (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
result
CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onWebContextUserMessageReceived :: (IsWebContext a, MonadIO m) => a -> ((?self :: a) => WebContextUserMessageReceivedCallback) -> m SignalHandlerId
onWebContextUserMessageReceived :: forall a (m :: * -> *).
(IsWebContext a, MonadIO m) =>
a
-> ((?self::a) => WebContextUserMessageReceivedCallback)
-> m SignalHandlerId
onWebContextUserMessageReceived a
obj (?self::a) => WebContextUserMessageReceivedCallback
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 -> WebContextUserMessageReceivedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => WebContextUserMessageReceivedCallback
WebContextUserMessageReceivedCallback
cb
let wrapped' :: C_WebContextUserMessageReceivedCallback
wrapped' = (a -> WebContextUserMessageReceivedCallback)
-> C_WebContextUserMessageReceivedCallback
forall a.
GObject a =>
(a -> WebContextUserMessageReceivedCallback)
-> C_WebContextUserMessageReceivedCallback
wrap_WebContextUserMessageReceivedCallback a -> WebContextUserMessageReceivedCallback
wrapped
FunPtr C_WebContextUserMessageReceivedCallback
wrapped'' <- C_WebContextUserMessageReceivedCallback
-> IO (FunPtr C_WebContextUserMessageReceivedCallback)
mk_WebContextUserMessageReceivedCallback C_WebContextUserMessageReceivedCallback
wrapped'
a
-> Text
-> FunPtr C_WebContextUserMessageReceivedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"user-message-received" FunPtr C_WebContextUserMessageReceivedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterWebContextUserMessageReceived :: (IsWebContext a, MonadIO m) => a -> ((?self :: a) => WebContextUserMessageReceivedCallback) -> m SignalHandlerId
afterWebContextUserMessageReceived :: forall a (m :: * -> *).
(IsWebContext a, MonadIO m) =>
a
-> ((?self::a) => WebContextUserMessageReceivedCallback)
-> m SignalHandlerId
afterWebContextUserMessageReceived a
obj (?self::a) => WebContextUserMessageReceivedCallback
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 -> WebContextUserMessageReceivedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => WebContextUserMessageReceivedCallback
WebContextUserMessageReceivedCallback
cb
let wrapped' :: C_WebContextUserMessageReceivedCallback
wrapped' = (a -> WebContextUserMessageReceivedCallback)
-> C_WebContextUserMessageReceivedCallback
forall a.
GObject a =>
(a -> WebContextUserMessageReceivedCallback)
-> C_WebContextUserMessageReceivedCallback
wrap_WebContextUserMessageReceivedCallback a -> WebContextUserMessageReceivedCallback
wrapped
FunPtr C_WebContextUserMessageReceivedCallback
wrapped'' <- C_WebContextUserMessageReceivedCallback
-> IO (FunPtr C_WebContextUserMessageReceivedCallback)
mk_WebContextUserMessageReceivedCallback C_WebContextUserMessageReceivedCallback
wrapped'
a
-> Text
-> FunPtr C_WebContextUserMessageReceivedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"user-message-received" FunPtr C_WebContextUserMessageReceivedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data WebContextUserMessageReceivedSignalInfo
instance SignalInfo WebContextUserMessageReceivedSignalInfo where
type HaskellCallbackType WebContextUserMessageReceivedSignalInfo = WebContextUserMessageReceivedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_WebContextUserMessageReceivedCallback cb
cb'' <- mk_WebContextUserMessageReceivedCallback cb'
connectSignalFunPtr obj "user-message-received" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext::user-message-received"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#g:signal:userMessageReceived"})
#endif
constructWebContextMemoryPressureSettings :: (IsWebContext o, MIO.MonadIO m) => WebKit.MemoryPressureSettings.MemoryPressureSettings -> m (GValueConstruct o)
constructWebContextMemoryPressureSettings :: forall o (m :: * -> *).
(IsWebContext o, MonadIO m) =>
MemoryPressureSettings -> m (GValueConstruct o)
constructWebContextMemoryPressureSettings MemoryPressureSettings
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 MemoryPressureSettings -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"memory-pressure-settings" (MemoryPressureSettings -> Maybe MemoryPressureSettings
forall a. a -> Maybe a
P.Just MemoryPressureSettings
val)
#if defined(ENABLE_OVERLOADING)
data WebContextMemoryPressureSettingsPropertyInfo
instance AttrInfo WebContextMemoryPressureSettingsPropertyInfo where
type AttrAllowedOps WebContextMemoryPressureSettingsPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint WebContextMemoryPressureSettingsPropertyInfo = IsWebContext
type AttrSetTypeConstraint WebContextMemoryPressureSettingsPropertyInfo = (~) WebKit.MemoryPressureSettings.MemoryPressureSettings
type AttrTransferTypeConstraint WebContextMemoryPressureSettingsPropertyInfo = (~) WebKit.MemoryPressureSettings.MemoryPressureSettings
type AttrTransferType WebContextMemoryPressureSettingsPropertyInfo = WebKit.MemoryPressureSettings.MemoryPressureSettings
type AttrGetType WebContextMemoryPressureSettingsPropertyInfo = ()
type AttrLabel WebContextMemoryPressureSettingsPropertyInfo = "memory-pressure-settings"
type AttrOrigin WebContextMemoryPressureSettingsPropertyInfo = WebContext
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructWebContextMemoryPressureSettings
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.memoryPressureSettings"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#g:attr:memoryPressureSettings"
})
#endif
getWebContextTimeZoneOverride :: (MonadIO m, IsWebContext o) => o -> m T.Text
getWebContextTimeZoneOverride :: forall (m :: * -> *) o. (MonadIO m, IsWebContext o) => o -> m Text
getWebContextTimeZoneOverride o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getWebContextTimeZoneOverride" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"time-zone-override"
constructWebContextTimeZoneOverride :: (IsWebContext o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructWebContextTimeZoneOverride :: forall o (m :: * -> *).
(IsWebContext o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructWebContextTimeZoneOverride 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
"time-zone-override" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data WebContextTimeZoneOverridePropertyInfo
instance AttrInfo WebContextTimeZoneOverridePropertyInfo where
type AttrAllowedOps WebContextTimeZoneOverridePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint WebContextTimeZoneOverridePropertyInfo = IsWebContext
type AttrSetTypeConstraint WebContextTimeZoneOverridePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint WebContextTimeZoneOverridePropertyInfo = (~) T.Text
type AttrTransferType WebContextTimeZoneOverridePropertyInfo = T.Text
type AttrGetType WebContextTimeZoneOverridePropertyInfo = T.Text
type AttrLabel WebContextTimeZoneOverridePropertyInfo = "time-zone-override"
type AttrOrigin WebContextTimeZoneOverridePropertyInfo = WebContext
attrGet = getWebContextTimeZoneOverride
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructWebContextTimeZoneOverride
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.timeZoneOverride"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#g:attr:timeZoneOverride"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WebContext
type instance O.AttributeList WebContext = WebContextAttributeList
type WebContextAttributeList = ('[ '("memoryPressureSettings", WebContextMemoryPressureSettingsPropertyInfo), '("timeZoneOverride", WebContextTimeZoneOverridePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
webContextMemoryPressureSettings :: AttrLabelProxy "memoryPressureSettings"
webContextMemoryPressureSettings = AttrLabelProxy
webContextTimeZoneOverride :: AttrLabelProxy "timeZoneOverride"
webContextTimeZoneOverride = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList WebContext = WebContextSignalList
type WebContextSignalList = ('[ '("automationStarted", WebContextAutomationStartedSignalInfo), '("initializeNotificationPermissions", WebContextInitializeNotificationPermissionsSignalInfo), '("initializeWebProcessExtensions", WebContextInitializeWebProcessExtensionsSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("userMessageReceived", WebContextUserMessageReceivedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "webkit_web_context_new" webkit_web_context_new ::
IO (Ptr WebContext)
webContextNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m WebContext
webContextNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m WebContext
webContextNew = IO WebContext -> m WebContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WebContext -> m WebContext) -> IO WebContext -> m WebContext
forall a b. (a -> b) -> a -> b
$ do
Ptr WebContext
result <- IO (Ptr WebContext)
webkit_web_context_new
Text -> Ptr WebContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"webContextNew" Ptr WebContext
result
WebContext
result' <- ((ManagedPtr WebContext -> WebContext)
-> Ptr WebContext -> IO WebContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr WebContext -> WebContext
WebContext) Ptr WebContext
result
WebContext -> IO WebContext
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WebContext
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "webkit_web_context_add_path_to_sandbox" webkit_web_context_add_path_to_sandbox ::
Ptr WebContext ->
CString ->
CInt ->
IO ()
webContextAddPathToSandbox ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> [Char]
-> Bool
-> m ()
webContextAddPathToSandbox :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> String -> Bool -> m ()
webContextAddPathToSandbox a
context String
path Bool
readOnly = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CString
path' <- String -> IO CString
stringToCString String
path
let readOnly' :: CInt
readOnly' = (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
readOnly
Ptr WebContext -> CString -> CInt -> IO ()
webkit_web_context_add_path_to_sandbox Ptr WebContext
context' CString
path' CInt
readOnly'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextAddPathToSandboxMethodInfo
instance (signature ~ ([Char] -> Bool -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextAddPathToSandboxMethodInfo a signature where
overloadedMethod = webContextAddPathToSandbox
instance O.OverloadedMethodInfo WebContextAddPathToSandboxMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextAddPathToSandbox",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextAddPathToSandbox"
})
#endif
foreign import ccall "webkit_web_context_get_cache_model" webkit_web_context_get_cache_model ::
Ptr WebContext ->
IO CUInt
webContextGetCacheModel ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> m WebKit.Enums.CacheModel
webContextGetCacheModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> m CacheModel
webContextGetCacheModel a
context = IO CacheModel -> m CacheModel
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CacheModel -> m CacheModel) -> IO CacheModel -> m CacheModel
forall a b. (a -> b) -> a -> b
$ do
Ptr WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CUInt
result <- Ptr WebContext -> IO CUInt
webkit_web_context_get_cache_model Ptr WebContext
context'
let result' :: CacheModel
result' = (Int -> CacheModel
forall a. Enum a => Int -> a
toEnum (Int -> CacheModel) -> (CUInt -> Int) -> CUInt -> CacheModel
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
context
CacheModel -> IO CacheModel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CacheModel
result'
#if defined(ENABLE_OVERLOADING)
data WebContextGetCacheModelMethodInfo
instance (signature ~ (m WebKit.Enums.CacheModel), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextGetCacheModelMethodInfo a signature where
overloadedMethod = webContextGetCacheModel
instance O.OverloadedMethodInfo WebContextGetCacheModelMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextGetCacheModel",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextGetCacheModel"
})
#endif
foreign import ccall "webkit_web_context_get_geolocation_manager" webkit_web_context_get_geolocation_manager ::
Ptr WebContext ->
IO (Ptr WebKit.GeolocationManager.GeolocationManager)
webContextGetGeolocationManager ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> m WebKit.GeolocationManager.GeolocationManager
webContextGetGeolocationManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> m GeolocationManager
webContextGetGeolocationManager a
context = IO GeolocationManager -> m GeolocationManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GeolocationManager -> m GeolocationManager)
-> IO GeolocationManager -> m GeolocationManager
forall a b. (a -> b) -> a -> b
$ do
Ptr WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr GeolocationManager
result <- Ptr WebContext -> IO (Ptr GeolocationManager)
webkit_web_context_get_geolocation_manager Ptr WebContext
context'
Text -> Ptr GeolocationManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"webContextGetGeolocationManager" Ptr GeolocationManager
result
GeolocationManager
result' <- ((ManagedPtr GeolocationManager -> GeolocationManager)
-> Ptr GeolocationManager -> IO GeolocationManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr GeolocationManager -> GeolocationManager
WebKit.GeolocationManager.GeolocationManager) Ptr GeolocationManager
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
GeolocationManager -> IO GeolocationManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GeolocationManager
result'
#if defined(ENABLE_OVERLOADING)
data WebContextGetGeolocationManagerMethodInfo
instance (signature ~ (m WebKit.GeolocationManager.GeolocationManager), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextGetGeolocationManagerMethodInfo a signature where
overloadedMethod = webContextGetGeolocationManager
instance O.OverloadedMethodInfo WebContextGetGeolocationManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextGetGeolocationManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextGetGeolocationManager"
})
#endif
foreign import ccall "webkit_web_context_get_network_session_for_automation" webkit_web_context_get_network_session_for_automation ::
Ptr WebContext ->
IO (Ptr WebKit.NetworkSession.NetworkSession)
webContextGetNetworkSessionForAutomation ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> m (Maybe WebKit.NetworkSession.NetworkSession)
webContextGetNetworkSessionForAutomation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> m (Maybe NetworkSession)
webContextGetNetworkSessionForAutomation a
context = IO (Maybe NetworkSession) -> m (Maybe NetworkSession)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe NetworkSession) -> m (Maybe NetworkSession))
-> IO (Maybe NetworkSession) -> m (Maybe NetworkSession)
forall a b. (a -> b) -> a -> b
$ do
Ptr WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr NetworkSession
result <- Ptr WebContext -> IO (Ptr NetworkSession)
webkit_web_context_get_network_session_for_automation Ptr WebContext
context'
Maybe NetworkSession
maybeResult <- Ptr NetworkSession
-> (Ptr NetworkSession -> IO NetworkSession)
-> IO (Maybe NetworkSession)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr NetworkSession
result ((Ptr NetworkSession -> IO NetworkSession)
-> IO (Maybe NetworkSession))
-> (Ptr NetworkSession -> IO NetworkSession)
-> IO (Maybe NetworkSession)
forall a b. (a -> b) -> a -> b
$ \Ptr NetworkSession
result' -> do
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
WebKit.NetworkSession.NetworkSession) Ptr NetworkSession
result'
NetworkSession -> IO NetworkSession
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return NetworkSession
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Maybe NetworkSession -> IO (Maybe NetworkSession)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NetworkSession
maybeResult
#if defined(ENABLE_OVERLOADING)
data WebContextGetNetworkSessionForAutomationMethodInfo
instance (signature ~ (m (Maybe WebKit.NetworkSession.NetworkSession)), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextGetNetworkSessionForAutomationMethodInfo a signature where
overloadedMethod = webContextGetNetworkSessionForAutomation
instance O.OverloadedMethodInfo WebContextGetNetworkSessionForAutomationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextGetNetworkSessionForAutomation",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextGetNetworkSessionForAutomation"
})
#endif
foreign import ccall "webkit_web_context_get_security_manager" webkit_web_context_get_security_manager ::
Ptr WebContext ->
IO (Ptr WebKit.SecurityManager.SecurityManager)
webContextGetSecurityManager ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> m WebKit.SecurityManager.SecurityManager
webContextGetSecurityManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> m SecurityManager
webContextGetSecurityManager a
context = IO SecurityManager -> m SecurityManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SecurityManager -> m SecurityManager)
-> IO SecurityManager -> m SecurityManager
forall a b. (a -> b) -> a -> b
$ do
Ptr WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr SecurityManager
result <- Ptr WebContext -> IO (Ptr SecurityManager)
webkit_web_context_get_security_manager Ptr WebContext
context'
Text -> Ptr SecurityManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"webContextGetSecurityManager" Ptr SecurityManager
result
SecurityManager
result' <- ((ManagedPtr SecurityManager -> SecurityManager)
-> Ptr SecurityManager -> IO SecurityManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr SecurityManager -> SecurityManager
WebKit.SecurityManager.SecurityManager) Ptr SecurityManager
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
SecurityManager -> IO SecurityManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SecurityManager
result'
#if defined(ENABLE_OVERLOADING)
data WebContextGetSecurityManagerMethodInfo
instance (signature ~ (m WebKit.SecurityManager.SecurityManager), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextGetSecurityManagerMethodInfo a signature where
overloadedMethod = webContextGetSecurityManager
instance O.OverloadedMethodInfo WebContextGetSecurityManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextGetSecurityManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextGetSecurityManager"
})
#endif
foreign import ccall "webkit_web_context_get_spell_checking_enabled" webkit_web_context_get_spell_checking_enabled ::
Ptr WebContext ->
IO CInt
webContextGetSpellCheckingEnabled ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> m Bool
webContextGetSpellCheckingEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> m Bool
webContextGetSpellCheckingEnabled a
context = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CInt
result <- Ptr WebContext -> IO CInt
webkit_web_context_get_spell_checking_enabled Ptr WebContext
context'
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
context
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data WebContextGetSpellCheckingEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextGetSpellCheckingEnabledMethodInfo a signature where
overloadedMethod = webContextGetSpellCheckingEnabled
instance O.OverloadedMethodInfo WebContextGetSpellCheckingEnabledMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextGetSpellCheckingEnabled",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextGetSpellCheckingEnabled"
})
#endif
foreign import ccall "webkit_web_context_get_spell_checking_languages" webkit_web_context_get_spell_checking_languages ::
Ptr WebContext ->
IO (Ptr CString)
webContextGetSpellCheckingLanguages ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> m [T.Text]
webContextGetSpellCheckingLanguages :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> m [Text]
webContextGetSpellCheckingLanguages a
context = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
Ptr WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr CString
result <- Ptr WebContext -> IO (Ptr CString)
webkit_web_context_get_spell_checking_languages Ptr WebContext
context'
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"webContextGetSpellCheckingLanguages" Ptr CString
result
[Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
[Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data WebContextGetSpellCheckingLanguagesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextGetSpellCheckingLanguagesMethodInfo a signature where
overloadedMethod = webContextGetSpellCheckingLanguages
instance O.OverloadedMethodInfo WebContextGetSpellCheckingLanguagesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextGetSpellCheckingLanguages",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextGetSpellCheckingLanguages"
})
#endif
foreign import ccall "webkit_web_context_get_time_zone_override" webkit_web_context_get_time_zone_override ::
Ptr WebContext ->
IO CString
webContextGetTimeZoneOverride ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> m T.Text
webContextGetTimeZoneOverride :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> m Text
webContextGetTimeZoneOverride a
context = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CString
result <- Ptr WebContext -> IO CString
webkit_web_context_get_time_zone_override Ptr WebContext
context'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"webContextGetTimeZoneOverride" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data WebContextGetTimeZoneOverrideMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextGetTimeZoneOverrideMethodInfo a signature where
overloadedMethod = webContextGetTimeZoneOverride
instance O.OverloadedMethodInfo WebContextGetTimeZoneOverrideMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextGetTimeZoneOverride",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextGetTimeZoneOverride"
})
#endif
foreign import ccall "webkit_web_context_initialize_notification_permissions" webkit_web_context_initialize_notification_permissions ::
Ptr WebContext ->
Ptr (GList (Ptr WebKit.SecurityOrigin.SecurityOrigin)) ->
Ptr (GList (Ptr WebKit.SecurityOrigin.SecurityOrigin)) ->
IO ()
webContextInitializeNotificationPermissions ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> [WebKit.SecurityOrigin.SecurityOrigin]
-> [WebKit.SecurityOrigin.SecurityOrigin]
-> m ()
webContextInitializeNotificationPermissions :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> [SecurityOrigin] -> [SecurityOrigin] -> m ()
webContextInitializeNotificationPermissions a
context [SecurityOrigin]
allowedOrigins [SecurityOrigin]
disallowedOrigins = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
[Ptr SecurityOrigin]
allowedOrigins' <- (SecurityOrigin -> IO (Ptr SecurityOrigin))
-> [SecurityOrigin] -> IO [Ptr SecurityOrigin]
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 SecurityOrigin -> IO (Ptr SecurityOrigin)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [SecurityOrigin]
allowedOrigins
Ptr (GList (Ptr SecurityOrigin))
allowedOrigins'' <- [Ptr SecurityOrigin] -> IO (Ptr (GList (Ptr SecurityOrigin)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr SecurityOrigin]
allowedOrigins'
[Ptr SecurityOrigin]
disallowedOrigins' <- (SecurityOrigin -> IO (Ptr SecurityOrigin))
-> [SecurityOrigin] -> IO [Ptr SecurityOrigin]
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 SecurityOrigin -> IO (Ptr SecurityOrigin)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [SecurityOrigin]
disallowedOrigins
Ptr (GList (Ptr SecurityOrigin))
disallowedOrigins'' <- [Ptr SecurityOrigin] -> IO (Ptr (GList (Ptr SecurityOrigin)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr SecurityOrigin]
disallowedOrigins'
Ptr WebContext
-> Ptr (GList (Ptr SecurityOrigin))
-> Ptr (GList (Ptr SecurityOrigin))
-> IO ()
webkit_web_context_initialize_notification_permissions Ptr WebContext
context' Ptr (GList (Ptr SecurityOrigin))
allowedOrigins'' Ptr (GList (Ptr SecurityOrigin))
disallowedOrigins''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
(SecurityOrigin -> IO ()) -> [SecurityOrigin] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ SecurityOrigin -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [SecurityOrigin]
allowedOrigins
(SecurityOrigin -> IO ()) -> [SecurityOrigin] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ SecurityOrigin -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [SecurityOrigin]
disallowedOrigins
Ptr (GList (Ptr SecurityOrigin)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr SecurityOrigin))
allowedOrigins''
Ptr (GList (Ptr SecurityOrigin)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr SecurityOrigin))
disallowedOrigins''
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextInitializeNotificationPermissionsMethodInfo
instance (signature ~ ([WebKit.SecurityOrigin.SecurityOrigin] -> [WebKit.SecurityOrigin.SecurityOrigin] -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextInitializeNotificationPermissionsMethodInfo a signature where
overloadedMethod = webContextInitializeNotificationPermissions
instance O.OverloadedMethodInfo WebContextInitializeNotificationPermissionsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextInitializeNotificationPermissions",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextInitializeNotificationPermissions"
})
#endif
foreign import ccall "webkit_web_context_is_automation_allowed" webkit_web_context_is_automation_allowed ::
Ptr WebContext ->
IO CInt
webContextIsAutomationAllowed ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> m Bool
webContextIsAutomationAllowed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> m Bool
webContextIsAutomationAllowed a
context = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CInt
result <- Ptr WebContext -> IO CInt
webkit_web_context_is_automation_allowed Ptr WebContext
context'
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
context
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data WebContextIsAutomationAllowedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextIsAutomationAllowedMethodInfo a signature where
overloadedMethod = webContextIsAutomationAllowed
instance O.OverloadedMethodInfo WebContextIsAutomationAllowedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextIsAutomationAllowed",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextIsAutomationAllowed"
})
#endif
foreign import ccall "webkit_web_context_register_uri_scheme" webkit_web_context_register_uri_scheme ::
Ptr WebContext ->
CString ->
FunPtr WebKit.Callbacks.C_URISchemeRequestCallback ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
webContextRegisterUriScheme ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> T.Text
-> WebKit.Callbacks.URISchemeRequestCallback
-> m ()
webContextRegisterUriScheme :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> Text -> URISchemeRequestCallback -> m ()
webContextRegisterUriScheme a
context Text
scheme URISchemeRequestCallback
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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CString
scheme' <- Text -> IO CString
textToCString Text
scheme
FunPtr C_URISchemeRequestCallback
callback' <- C_URISchemeRequestCallback
-> IO (FunPtr C_URISchemeRequestCallback)
WebKit.Callbacks.mk_URISchemeRequestCallback (Maybe (Ptr (FunPtr C_URISchemeRequestCallback))
-> URISchemeRequestCallback_WithClosures
-> C_URISchemeRequestCallback
WebKit.Callbacks.wrap_URISchemeRequestCallback Maybe (Ptr (FunPtr C_URISchemeRequestCallback))
forall a. Maybe a
Nothing (URISchemeRequestCallback -> URISchemeRequestCallback_WithClosures
WebKit.Callbacks.drop_closures_URISchemeRequestCallback URISchemeRequestCallback
callback))
let userData :: Ptr ()
userData = FunPtr C_URISchemeRequestCallback -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_URISchemeRequestCallback
callback'
let userDataDestroyFunc :: FunPtr (Ptr a -> IO ())
userDataDestroyFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
Ptr WebContext
-> CString
-> FunPtr C_URISchemeRequestCallback
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
webkit_web_context_register_uri_scheme Ptr WebContext
context' CString
scheme' FunPtr C_URISchemeRequestCallback
callback' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
userDataDestroyFunc
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
scheme'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextRegisterUriSchemeMethodInfo
instance (signature ~ (T.Text -> WebKit.Callbacks.URISchemeRequestCallback -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextRegisterUriSchemeMethodInfo a signature where
overloadedMethod = webContextRegisterUriScheme
instance O.OverloadedMethodInfo WebContextRegisterUriSchemeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextRegisterUriScheme",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextRegisterUriScheme"
})
#endif
foreign import ccall "webkit_web_context_send_message_to_all_extensions" webkit_web_context_send_message_to_all_extensions ::
Ptr WebContext ->
Ptr WebKit.UserMessage.UserMessage ->
IO ()
webContextSendMessageToAllExtensions ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a, WebKit.UserMessage.IsUserMessage b) =>
a
-> b
-> m ()
webContextSendMessageToAllExtensions :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebContext a, IsUserMessage b) =>
a -> b -> m ()
webContextSendMessageToAllExtensions a
context b
message = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr UserMessage
message' <- b -> IO (Ptr UserMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
message
Ptr WebContext -> Ptr UserMessage -> IO ()
webkit_web_context_send_message_to_all_extensions Ptr WebContext
context' Ptr UserMessage
message'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
message
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextSendMessageToAllExtensionsMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsWebContext a, WebKit.UserMessage.IsUserMessage b) => O.OverloadedMethod WebContextSendMessageToAllExtensionsMethodInfo a signature where
overloadedMethod = webContextSendMessageToAllExtensions
instance O.OverloadedMethodInfo WebContextSendMessageToAllExtensionsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextSendMessageToAllExtensions",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextSendMessageToAllExtensions"
})
#endif
foreign import ccall "webkit_web_context_set_automation_allowed" webkit_web_context_set_automation_allowed ::
Ptr WebContext ->
CInt ->
IO ()
webContextSetAutomationAllowed ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> Bool
-> m ()
webContextSetAutomationAllowed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> Bool -> m ()
webContextSetAutomationAllowed a
context Bool
allowed = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
let allowed' :: CInt
allowed' = (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
allowed
Ptr WebContext -> CInt -> IO ()
webkit_web_context_set_automation_allowed Ptr WebContext
context' CInt
allowed'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextSetAutomationAllowedMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextSetAutomationAllowedMethodInfo a signature where
overloadedMethod = webContextSetAutomationAllowed
instance O.OverloadedMethodInfo WebContextSetAutomationAllowedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextSetAutomationAllowed",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextSetAutomationAllowed"
})
#endif
foreign import ccall "webkit_web_context_set_cache_model" webkit_web_context_set_cache_model ::
Ptr WebContext ->
CUInt ->
IO ()
webContextSetCacheModel ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> WebKit.Enums.CacheModel
-> m ()
webContextSetCacheModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> CacheModel -> m ()
webContextSetCacheModel a
context CacheModel
cacheModel = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
let cacheModel' :: CUInt
cacheModel' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CacheModel -> Int) -> CacheModel -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CacheModel -> Int
forall a. Enum a => a -> Int
fromEnum) CacheModel
cacheModel
Ptr WebContext -> CUInt -> IO ()
webkit_web_context_set_cache_model Ptr WebContext
context' CUInt
cacheModel'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextSetCacheModelMethodInfo
instance (signature ~ (WebKit.Enums.CacheModel -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextSetCacheModelMethodInfo a signature where
overloadedMethod = webContextSetCacheModel
instance O.OverloadedMethodInfo WebContextSetCacheModelMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextSetCacheModel",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextSetCacheModel"
})
#endif
foreign import ccall "webkit_web_context_set_preferred_languages" webkit_web_context_set_preferred_languages ::
Ptr WebContext ->
Ptr CString ->
IO ()
webContextSetPreferredLanguages ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> Maybe ([T.Text])
-> m ()
webContextSetPreferredLanguages :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> Maybe [Text] -> m ()
webContextSetPreferredLanguages a
context Maybe [Text]
languages = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr CString
maybeLanguages <- case Maybe [Text]
languages of
Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
Just [Text]
jLanguages -> do
Ptr CString
jLanguages' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jLanguages
Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jLanguages'
Ptr WebContext -> Ptr CString -> IO ()
webkit_web_context_set_preferred_languages Ptr WebContext
context' Ptr CString
maybeLanguages
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeLanguages
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeLanguages
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextSetPreferredLanguagesMethodInfo
instance (signature ~ (Maybe ([T.Text]) -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextSetPreferredLanguagesMethodInfo a signature where
overloadedMethod = webContextSetPreferredLanguages
instance O.OverloadedMethodInfo WebContextSetPreferredLanguagesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextSetPreferredLanguages",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextSetPreferredLanguages"
})
#endif
foreign import ccall "webkit_web_context_set_spell_checking_enabled" webkit_web_context_set_spell_checking_enabled ::
Ptr WebContext ->
CInt ->
IO ()
webContextSetSpellCheckingEnabled ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> Bool
-> m ()
webContextSetSpellCheckingEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> Bool -> m ()
webContextSetSpellCheckingEnabled a
context 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
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 WebContext -> CInt -> IO ()
webkit_web_context_set_spell_checking_enabled Ptr WebContext
context' CInt
enabled'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextSetSpellCheckingEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextSetSpellCheckingEnabledMethodInfo a signature where
overloadedMethod = webContextSetSpellCheckingEnabled
instance O.OverloadedMethodInfo WebContextSetSpellCheckingEnabledMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextSetSpellCheckingEnabled",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextSetSpellCheckingEnabled"
})
#endif
foreign import ccall "webkit_web_context_set_spell_checking_languages" webkit_web_context_set_spell_checking_languages ::
Ptr WebContext ->
Ptr CString ->
IO ()
webContextSetSpellCheckingLanguages ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> [T.Text]
-> m ()
webContextSetSpellCheckingLanguages :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> [Text] -> m ()
webContextSetSpellCheckingLanguages a
context [Text]
languages = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr CString
languages' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
languages
Ptr WebContext -> Ptr CString -> IO ()
webkit_web_context_set_spell_checking_languages Ptr WebContext
context' Ptr CString
languages'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
languages'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
languages'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextSetSpellCheckingLanguagesMethodInfo
instance (signature ~ ([T.Text] -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextSetSpellCheckingLanguagesMethodInfo a signature where
overloadedMethod = webContextSetSpellCheckingLanguages
instance O.OverloadedMethodInfo WebContextSetSpellCheckingLanguagesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextSetSpellCheckingLanguages",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextSetSpellCheckingLanguages"
})
#endif
foreign import ccall "webkit_web_context_set_web_process_extensions_directory" webkit_web_context_set_web_process_extensions_directory ::
Ptr WebContext ->
CString ->
IO ()
webContextSetWebProcessExtensionsDirectory ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> T.Text
-> m ()
webContextSetWebProcessExtensionsDirectory :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> Text -> m ()
webContextSetWebProcessExtensionsDirectory a
context Text
directory = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CString
directory' <- Text -> IO CString
textToCString Text
directory
Ptr WebContext -> CString -> IO ()
webkit_web_context_set_web_process_extensions_directory Ptr WebContext
context' CString
directory'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
directory'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextSetWebProcessExtensionsDirectoryMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextSetWebProcessExtensionsDirectoryMethodInfo a signature where
overloadedMethod = webContextSetWebProcessExtensionsDirectory
instance O.OverloadedMethodInfo WebContextSetWebProcessExtensionsDirectoryMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextSetWebProcessExtensionsDirectory",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextSetWebProcessExtensionsDirectory"
})
#endif
foreign import ccall "webkit_web_context_set_web_process_extensions_initialization_user_data" webkit_web_context_set_web_process_extensions_initialization_user_data ::
Ptr WebContext ->
Ptr GVariant ->
IO ()
webContextSetWebProcessExtensionsInitializationUserData ::
(B.CallStack.HasCallStack, MonadIO m, IsWebContext a) =>
a
-> GVariant
-> m ()
webContextSetWebProcessExtensionsInitializationUserData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebContext a) =>
a -> GVariant -> m ()
webContextSetWebProcessExtensionsInitializationUserData a
context GVariant
userData = 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 WebContext
context' <- a -> IO (Ptr WebContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr GVariant
userData' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
userData
Ptr WebContext -> Ptr GVariant -> IO ()
webkit_web_context_set_web_process_extensions_initialization_user_data Ptr WebContext
context' Ptr GVariant
userData'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
userData
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebContextSetWebProcessExtensionsInitializationUserDataMethodInfo
instance (signature ~ (GVariant -> m ()), MonadIO m, IsWebContext a) => O.OverloadedMethod WebContextSetWebProcessExtensionsInitializationUserDataMethodInfo a signature where
overloadedMethod = webContextSetWebProcessExtensionsInitializationUserData
instance O.OverloadedMethodInfo WebContextSetWebProcessExtensionsInitializationUserDataMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.WebContext.webContextSetWebProcessExtensionsInitializationUserData",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-WebContext.html#v:webContextSetWebProcessExtensionsInitializationUserData"
})
#endif
foreign import ccall "webkit_web_context_get_default" webkit_web_context_get_default ::
IO (Ptr WebContext)
webContextGetDefault ::
(B.CallStack.HasCallStack, MonadIO m) =>
m WebContext
webContextGetDefault :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m WebContext
webContextGetDefault = IO WebContext -> m WebContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WebContext -> m WebContext) -> IO WebContext -> m WebContext
forall a b. (a -> b) -> a -> b
$ do
Ptr WebContext
result <- IO (Ptr WebContext)
webkit_web_context_get_default
Text -> Ptr WebContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"webContextGetDefault" Ptr WebContext
result
WebContext
result' <- ((ManagedPtr WebContext -> WebContext)
-> Ptr WebContext -> IO WebContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr WebContext -> WebContext
WebContext) Ptr WebContext
result
WebContext -> IO WebContext
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WebContext
result'
#if defined(ENABLE_OVERLOADING)
#endif