{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Manages data stored locally by web sites.
-- 
-- You can use WebKitWebsiteDataManager to configure the local directories
-- where website data will be stored. Use [WebsiteDataManager:baseDataDirectory]("GI.WebKit.Objects.WebsiteDataManager#g:attr:baseDataDirectory")
-- and [WebsiteDataManager:baseCacheDirectory]("GI.WebKit.Objects.WebsiteDataManager#g:attr:baseCacheDirectory") set a common base directory for all
-- website data and caches. The newly created WebKitWebsiteDataManager must be passed as
-- a construct property to a t'GI.WebKit.Objects.WebContext.WebContext'; you can use @/webkit_web_context_new_with_website_data_manager()/@
-- to create a new t'GI.WebKit.Objects.WebContext.WebContext' with a WebKitWebsiteDataManager.
-- If you don\'t want to set any specific configuration, you don\'t need to create
-- a WebKitWebsiteDataManager: the t'GI.WebKit.Objects.WebContext.WebContext' will create a WebKitWebsiteDataManager
-- with the default configuration. To get the WebKitWebsiteDataManager of a t'GI.WebKit.Objects.WebContext.WebContext',
-- you can use @/webkit_web_context_get_website_data_manager()/@.
-- 
-- A WebKitWebsiteDataManager can also be ephemeral, in which case all the directory configuration
-- is not needed because website data will never persist. You can create an ephemeral WebKitWebsiteDataManager
-- with @/webkit_website_data_manager_new_ephemeral()/@ and pass the ephemeral WebKitWebsiteDataManager to
-- a t'GI.WebKit.Objects.WebContext.WebContext', or simply use @/webkit_web_context_new_ephemeral()/@.
-- 
-- WebKitWebsiteDataManager can also be used to fetch website data, remove data
-- stored by particular websites, or clear data for all websites modified since a given
-- period of time.
-- 
-- /Since: 2.10/

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

module GI.WebKit.Objects.WebsiteDataManager
    ( 

-- * Exported types
    WebsiteDataManager(..)                  ,
    IsWebsiteDataManager                    ,
    toWebsiteDataManager                    ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clear]("GI.WebKit.Objects.WebsiteDataManager#g:method:clear"), [clearFinish]("GI.WebKit.Objects.WebsiteDataManager#g:method:clearFinish"), [fetch]("GI.WebKit.Objects.WebsiteDataManager#g:method:fetch"), [fetchFinish]("GI.WebKit.Objects.WebsiteDataManager#g:method:fetchFinish"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isEphemeral]("GI.WebKit.Objects.WebsiteDataManager#g:method:isEphemeral"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [remove]("GI.WebKit.Objects.WebsiteDataManager#g:method:remove"), [removeFinish]("GI.WebKit.Objects.WebsiteDataManager#g:method:removeFinish"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBaseCacheDirectory]("GI.WebKit.Objects.WebsiteDataManager#g:method:getBaseCacheDirectory"), [getBaseDataDirectory]("GI.WebKit.Objects.WebsiteDataManager#g:method:getBaseDataDirectory"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFaviconDatabase]("GI.WebKit.Objects.WebsiteDataManager#g:method:getFaviconDatabase"), [getFaviconsEnabled]("GI.WebKit.Objects.WebsiteDataManager#g:method:getFaviconsEnabled"), [getItpSummary]("GI.WebKit.Objects.WebsiteDataManager#g:method:getItpSummary"), [getItpSummaryFinish]("GI.WebKit.Objects.WebsiteDataManager#g:method:getItpSummaryFinish"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setFaviconsEnabled]("GI.WebKit.Objects.WebsiteDataManager#g:method:setFaviconsEnabled"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveWebsiteDataManagerMethod         ,
#endif

-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerClearMethodInfo       ,
#endif
    websiteDataManagerClear                 ,


-- ** clearFinish #method:clearFinish#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerClearFinishMethodInfo ,
#endif
    websiteDataManagerClearFinish           ,


-- ** fetch #method:fetch#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerFetchMethodInfo       ,
#endif
    websiteDataManagerFetch                 ,


-- ** fetchFinish #method:fetchFinish#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerFetchFinishMethodInfo ,
#endif
    websiteDataManagerFetchFinish           ,


-- ** getBaseCacheDirectory #method:getBaseCacheDirectory#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerGetBaseCacheDirectoryMethodInfo,
#endif
    websiteDataManagerGetBaseCacheDirectory ,


-- ** getBaseDataDirectory #method:getBaseDataDirectory#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerGetBaseDataDirectoryMethodInfo,
#endif
    websiteDataManagerGetBaseDataDirectory  ,


-- ** getFaviconDatabase #method:getFaviconDatabase#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerGetFaviconDatabaseMethodInfo,
#endif
    websiteDataManagerGetFaviconDatabase    ,


-- ** getFaviconsEnabled #method:getFaviconsEnabled#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerGetFaviconsEnabledMethodInfo,
#endif
    websiteDataManagerGetFaviconsEnabled    ,


-- ** getItpSummary #method:getItpSummary#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerGetItpSummaryMethodInfo,
#endif
    websiteDataManagerGetItpSummary         ,


-- ** getItpSummaryFinish #method:getItpSummaryFinish#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerGetItpSummaryFinishMethodInfo,
#endif
    websiteDataManagerGetItpSummaryFinish   ,


-- ** isEphemeral #method:isEphemeral#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerIsEphemeralMethodInfo ,
#endif
    websiteDataManagerIsEphemeral           ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerRemoveMethodInfo      ,
#endif
    websiteDataManagerRemove                ,


-- ** removeFinish #method:removeFinish#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerRemoveFinishMethodInfo,
#endif
    websiteDataManagerRemoveFinish          ,


-- ** setFaviconsEnabled #method:setFaviconsEnabled#

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerSetFaviconsEnabledMethodInfo,
#endif
    websiteDataManagerSetFaviconsEnabled    ,




 -- * Properties


-- ** baseCacheDirectory #attr:baseCacheDirectory#
-- | The base directory for caches. If 'P.Nothing', a default location will be used.
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerBaseCacheDirectoryPropertyInfo,
#endif
    constructWebsiteDataManagerBaseCacheDirectory,
    getWebsiteDataManagerBaseCacheDirectory ,
#if defined(ENABLE_OVERLOADING)
    websiteDataManagerBaseCacheDirectory    ,
#endif


-- ** baseDataDirectory #attr:baseDataDirectory#
-- | The base directory for website data. If 'P.Nothing', a default location will be used.
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerBaseDataDirectoryPropertyInfo,
#endif
    constructWebsiteDataManagerBaseDataDirectory,
    getWebsiteDataManagerBaseDataDirectory  ,
#if defined(ENABLE_OVERLOADING)
    websiteDataManagerBaseDataDirectory     ,
#endif


-- ** isEphemeral #attr:isEphemeral#
-- | Whether the t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager' is ephemeral. An ephemeral t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
-- handles all websites data as non-persistent, and nothing will be written to the client
-- storage. Note that if you create an ephemeral t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager' all other construction
-- parameters to configure data directories will be ignored.
-- 
-- /Since: 2.16/

#if defined(ENABLE_OVERLOADING)
    WebsiteDataManagerIsEphemeralPropertyInfo,
#endif
    constructWebsiteDataManagerIsEphemeral  ,
    getWebsiteDataManagerIsEphemeral        ,




    ) 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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.WebKit.Flags as WebKit.Flags
import {-# SOURCE #-} qualified GI.WebKit.Objects.FaviconDatabase as WebKit.FaviconDatabase
import {-# SOURCE #-} qualified GI.WebKit.Structs.ITPThirdParty as WebKit.ITPThirdParty
import {-# SOURCE #-} qualified GI.WebKit.Structs.WebsiteData as WebKit.WebsiteData

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

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

foreign import ccall "webkit_website_data_manager_get_type"
    c_webkit_website_data_manager_get_type :: IO B.Types.GType

instance B.Types.TypedObject WebsiteDataManager where
    glibType :: IO GType
glibType = IO GType
c_webkit_website_data_manager_get_type

instance B.Types.GObject WebsiteDataManager

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

instance O.HasParentTypes WebsiteDataManager
type instance O.ParentTypes WebsiteDataManager = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveWebsiteDataManagerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveWebsiteDataManagerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveWebsiteDataManagerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveWebsiteDataManagerMethod "clear" o = WebsiteDataManagerClearMethodInfo
    ResolveWebsiteDataManagerMethod "clearFinish" o = WebsiteDataManagerClearFinishMethodInfo
    ResolveWebsiteDataManagerMethod "fetch" o = WebsiteDataManagerFetchMethodInfo
    ResolveWebsiteDataManagerMethod "fetchFinish" o = WebsiteDataManagerFetchFinishMethodInfo
    ResolveWebsiteDataManagerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveWebsiteDataManagerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveWebsiteDataManagerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveWebsiteDataManagerMethod "isEphemeral" o = WebsiteDataManagerIsEphemeralMethodInfo
    ResolveWebsiteDataManagerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveWebsiteDataManagerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveWebsiteDataManagerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveWebsiteDataManagerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveWebsiteDataManagerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveWebsiteDataManagerMethod "remove" o = WebsiteDataManagerRemoveMethodInfo
    ResolveWebsiteDataManagerMethod "removeFinish" o = WebsiteDataManagerRemoveFinishMethodInfo
    ResolveWebsiteDataManagerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveWebsiteDataManagerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveWebsiteDataManagerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveWebsiteDataManagerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveWebsiteDataManagerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveWebsiteDataManagerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveWebsiteDataManagerMethod "getBaseCacheDirectory" o = WebsiteDataManagerGetBaseCacheDirectoryMethodInfo
    ResolveWebsiteDataManagerMethod "getBaseDataDirectory" o = WebsiteDataManagerGetBaseDataDirectoryMethodInfo
    ResolveWebsiteDataManagerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveWebsiteDataManagerMethod "getFaviconDatabase" o = WebsiteDataManagerGetFaviconDatabaseMethodInfo
    ResolveWebsiteDataManagerMethod "getFaviconsEnabled" o = WebsiteDataManagerGetFaviconsEnabledMethodInfo
    ResolveWebsiteDataManagerMethod "getItpSummary" o = WebsiteDataManagerGetItpSummaryMethodInfo
    ResolveWebsiteDataManagerMethod "getItpSummaryFinish" o = WebsiteDataManagerGetItpSummaryFinishMethodInfo
    ResolveWebsiteDataManagerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveWebsiteDataManagerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveWebsiteDataManagerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveWebsiteDataManagerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveWebsiteDataManagerMethod "setFaviconsEnabled" o = WebsiteDataManagerSetFaviconsEnabledMethodInfo
    ResolveWebsiteDataManagerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveWebsiteDataManagerMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveWebsiteDataManagerMethod t WebsiteDataManager, O.OverloadedMethod info WebsiteDataManager p) => OL.IsLabel t (WebsiteDataManager -> 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 ~ ResolveWebsiteDataManagerMethod t WebsiteDataManager, O.OverloadedMethod info WebsiteDataManager p, R.HasField t WebsiteDataManager p) => R.HasField t WebsiteDataManager p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "base-cache-directory"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@base-cache-directory@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' websiteDataManager #baseCacheDirectory
-- @
getWebsiteDataManagerBaseCacheDirectory :: (MonadIO m, IsWebsiteDataManager o) => o -> m (Maybe T.Text)
getWebsiteDataManagerBaseCacheDirectory :: forall (m :: * -> *) o.
(MonadIO m, IsWebsiteDataManager o) =>
o -> m (Maybe Text)
getWebsiteDataManagerBaseCacheDirectory o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"base-cache-directory"

-- | Construct a `GValueConstruct` with valid value for the “@base-cache-directory@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructWebsiteDataManagerBaseCacheDirectory :: (IsWebsiteDataManager o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructWebsiteDataManagerBaseCacheDirectory :: forall o (m :: * -> *).
(IsWebsiteDataManager o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructWebsiteDataManagerBaseCacheDirectory 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
"base-cache-directory" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerBaseCacheDirectoryPropertyInfo
instance AttrInfo WebsiteDataManagerBaseCacheDirectoryPropertyInfo where
    type AttrAllowedOps WebsiteDataManagerBaseCacheDirectoryPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint WebsiteDataManagerBaseCacheDirectoryPropertyInfo = IsWebsiteDataManager
    type AttrSetTypeConstraint WebsiteDataManagerBaseCacheDirectoryPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint WebsiteDataManagerBaseCacheDirectoryPropertyInfo = (~) T.Text
    type AttrTransferType WebsiteDataManagerBaseCacheDirectoryPropertyInfo = T.Text
    type AttrGetType WebsiteDataManagerBaseCacheDirectoryPropertyInfo = (Maybe T.Text)
    type AttrLabel WebsiteDataManagerBaseCacheDirectoryPropertyInfo = "base-cache-directory"
    type AttrOrigin WebsiteDataManagerBaseCacheDirectoryPropertyInfo = WebsiteDataManager
    attrGet = getWebsiteDataManagerBaseCacheDirectory
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructWebsiteDataManagerBaseCacheDirectory
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.baseCacheDirectory"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#g:attr:baseCacheDirectory"
        })
#endif

-- VVV Prop "base-data-directory"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@base-data-directory@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' websiteDataManager #baseDataDirectory
-- @
getWebsiteDataManagerBaseDataDirectory :: (MonadIO m, IsWebsiteDataManager o) => o -> m (Maybe T.Text)
getWebsiteDataManagerBaseDataDirectory :: forall (m :: * -> *) o.
(MonadIO m, IsWebsiteDataManager o) =>
o -> m (Maybe Text)
getWebsiteDataManagerBaseDataDirectory o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"base-data-directory"

-- | Construct a `GValueConstruct` with valid value for the “@base-data-directory@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructWebsiteDataManagerBaseDataDirectory :: (IsWebsiteDataManager o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructWebsiteDataManagerBaseDataDirectory :: forall o (m :: * -> *).
(IsWebsiteDataManager o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructWebsiteDataManagerBaseDataDirectory 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
"base-data-directory" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerBaseDataDirectoryPropertyInfo
instance AttrInfo WebsiteDataManagerBaseDataDirectoryPropertyInfo where
    type AttrAllowedOps WebsiteDataManagerBaseDataDirectoryPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint WebsiteDataManagerBaseDataDirectoryPropertyInfo = IsWebsiteDataManager
    type AttrSetTypeConstraint WebsiteDataManagerBaseDataDirectoryPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint WebsiteDataManagerBaseDataDirectoryPropertyInfo = (~) T.Text
    type AttrTransferType WebsiteDataManagerBaseDataDirectoryPropertyInfo = T.Text
    type AttrGetType WebsiteDataManagerBaseDataDirectoryPropertyInfo = (Maybe T.Text)
    type AttrLabel WebsiteDataManagerBaseDataDirectoryPropertyInfo = "base-data-directory"
    type AttrOrigin WebsiteDataManagerBaseDataDirectoryPropertyInfo = WebsiteDataManager
    attrGet = getWebsiteDataManagerBaseDataDirectory
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructWebsiteDataManagerBaseDataDirectory
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.baseDataDirectory"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#g:attr:baseDataDirectory"
        })
#endif

-- VVV Prop "is-ephemeral"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@is-ephemeral@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' websiteDataManager #isEphemeral
-- @
getWebsiteDataManagerIsEphemeral :: (MonadIO m, IsWebsiteDataManager o) => o -> m Bool
getWebsiteDataManagerIsEphemeral :: forall (m :: * -> *) o.
(MonadIO m, IsWebsiteDataManager o) =>
o -> m Bool
getWebsiteDataManagerIsEphemeral o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"is-ephemeral"

-- | Construct a `GValueConstruct` with valid value for the “@is-ephemeral@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructWebsiteDataManagerIsEphemeral :: (IsWebsiteDataManager o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructWebsiteDataManagerIsEphemeral :: forall o (m :: * -> *).
(IsWebsiteDataManager o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructWebsiteDataManagerIsEphemeral Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"is-ephemeral" Bool
val

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerIsEphemeralPropertyInfo
instance AttrInfo WebsiteDataManagerIsEphemeralPropertyInfo where
    type AttrAllowedOps WebsiteDataManagerIsEphemeralPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint WebsiteDataManagerIsEphemeralPropertyInfo = IsWebsiteDataManager
    type AttrSetTypeConstraint WebsiteDataManagerIsEphemeralPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint WebsiteDataManagerIsEphemeralPropertyInfo = (~) Bool
    type AttrTransferType WebsiteDataManagerIsEphemeralPropertyInfo = Bool
    type AttrGetType WebsiteDataManagerIsEphemeralPropertyInfo = Bool
    type AttrLabel WebsiteDataManagerIsEphemeralPropertyInfo = "is-ephemeral"
    type AttrOrigin WebsiteDataManagerIsEphemeralPropertyInfo = WebsiteDataManager
    attrGet = getWebsiteDataManagerIsEphemeral
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructWebsiteDataManagerIsEphemeral
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.isEphemeral"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#g:attr:isEphemeral"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WebsiteDataManager
type instance O.AttributeList WebsiteDataManager = WebsiteDataManagerAttributeList
type WebsiteDataManagerAttributeList = ('[ '("baseCacheDirectory", WebsiteDataManagerBaseCacheDirectoryPropertyInfo), '("baseDataDirectory", WebsiteDataManagerBaseDataDirectoryPropertyInfo), '("isEphemeral", WebsiteDataManagerIsEphemeralPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
websiteDataManagerBaseCacheDirectory :: AttrLabelProxy "baseCacheDirectory"
websiteDataManagerBaseCacheDirectory = AttrLabelProxy

websiteDataManagerBaseDataDirectory :: AttrLabelProxy "baseDataDirectory"
websiteDataManagerBaseDataDirectory = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList WebsiteDataManager = WebsiteDataManagerSignalList
type WebsiteDataManagerSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method WebsiteDataManager::clear
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "types"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataTypes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#WebKitWebsiteDataTypes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timespan"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTimeSpan" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GAsyncReadyCallback to call when the request is satisfied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_clear" webkit_website_data_manager_clear :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    CUInt ->                                -- types : TInterface (Name {namespace = "WebKit", name = "WebsiteDataTypes"})
    Int64 ->                                -- timespan : TBasicType TInt64
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously clear the website data of the given /@types@/ modified in the past /@timespan@/.
-- 
-- If /@timespan@/ is 0, all website data will be removed.
-- 
-- When the operation is finished, /@callback@/ will be called. You can then call
-- 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerClearFinish' to get the result of the operation.
-- 
-- Due to implementation limitations, this function does not currently delete
-- any stored cookies if /@timespan@/ is nonzero. This behavior may change in the
-- future.
-- 
-- /Since: 2.16/
websiteDataManagerClear ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> [WebKit.Flags.WebsiteDataTypes]
    -- ^ /@types@/: t'GI.WebKit.Flags.WebsiteDataTypes'
    -> Int64
    -- ^ /@timespan@/: a @/GTimeSpan/@
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing' to ignore
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is satisfied
    -> m ()
websiteDataManagerClear :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebsiteDataManager a,
 IsCancellable b) =>
a
-> [WebsiteDataTypes]
-> Int64
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
websiteDataManagerClear a
manager [WebsiteDataTypes]
types Int64
timespan Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    let types' :: CUInt
types' = [WebsiteDataTypes] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [WebsiteDataTypes]
types
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) AsyncReadyCallback
jCallback)
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr WebsiteDataManager
-> CUInt
-> Int64
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
webkit_website_data_manager_clear Ptr WebsiteDataManager
manager' CUInt
types' Int64
timespan Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerClearMethodInfo
instance (signature ~ ([WebKit.Flags.WebsiteDataTypes] -> Int64 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsWebsiteDataManager a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod WebsiteDataManagerClearMethodInfo a signature where
    overloadedMethod = websiteDataManagerClear

instance O.OverloadedMethodInfo WebsiteDataManagerClearMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerClear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerClear"
        })


#endif

-- method WebsiteDataManager::clear_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncResult" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "webkit_website_data_manager_clear_finish" webkit_website_data_manager_clear_finish :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finish an asynchronous operation started with 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerClear'
-- 
-- /Since: 2.16/
websiteDataManagerClearFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
websiteDataManagerClearFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebsiteDataManager a,
 IsAsyncResult b) =>
a -> b -> m ()
websiteDataManagerClearFinish a
manager b
result_ = 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 WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr WebsiteDataManager
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
webkit_website_data_manager_clear_finish Ptr WebsiteDataManager
manager' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerClearFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsWebsiteDataManager a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod WebsiteDataManagerClearFinishMethodInfo a signature where
    overloadedMethod = websiteDataManagerClearFinish

instance O.OverloadedMethodInfo WebsiteDataManagerClearFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerClearFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerClearFinish"
        })


#endif

-- method WebsiteDataManager::fetch
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "types"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataTypes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#WebKitWebsiteDataTypes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GAsyncReadyCallback to call when the request is satisfied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 4
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_fetch" webkit_website_data_manager_fetch :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    CUInt ->                                -- types : TInterface (Name {namespace = "WebKit", name = "WebsiteDataTypes"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously get the list of t'GI.WebKit.Structs.WebsiteData.WebsiteData' for the given /@types@/.
-- 
-- When the operation is finished, /@callback@/ will be called. You can then call
-- 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerFetchFinish' to get the result of the operation.
-- 
-- /Since: 2.16/
websiteDataManagerFetch ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> [WebKit.Flags.WebsiteDataTypes]
    -- ^ /@types@/: t'GI.WebKit.Flags.WebsiteDataTypes'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing' to ignore
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is satisfied
    -> m ()
websiteDataManagerFetch :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebsiteDataManager a,
 IsCancellable b) =>
a
-> [WebsiteDataTypes]
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
websiteDataManagerFetch a
manager [WebsiteDataTypes]
types Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    let types' :: CUInt
types' = [WebsiteDataTypes] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [WebsiteDataTypes]
types
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) AsyncReadyCallback
jCallback)
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr WebsiteDataManager
-> CUInt
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
webkit_website_data_manager_fetch Ptr WebsiteDataManager
manager' CUInt
types' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerFetchMethodInfo
instance (signature ~ ([WebKit.Flags.WebsiteDataTypes] -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsWebsiteDataManager a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod WebsiteDataManagerFetchMethodInfo a signature where
    overloadedMethod = websiteDataManagerFetch

instance O.OverloadedMethodInfo WebsiteDataManagerFetchMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerFetch",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerFetch"
        })


#endif

-- method WebsiteDataManager::fetch_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncResult" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "WebKit" , name = "WebsiteData" }))
-- throws : True
-- Skip return : False

foreign import ccall "webkit_website_data_manager_fetch_finish" webkit_website_data_manager_fetch_finish :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr (GList (Ptr WebKit.WebsiteData.WebsiteData)))

-- | Finish an asynchronous operation started with 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerFetch'.
-- 
-- /Since: 2.16/
websiteDataManagerFetchFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'
    -> m [WebKit.WebsiteData.WebsiteData]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of t'GI.WebKit.Structs.WebsiteData.WebsiteData'. You must free the t'GI.GLib.Structs.List.List' with
    --    @/g_list_free()/@ and unref the t'GI.WebKit.Structs.WebsiteData.WebsiteData's with 'GI.WebKit.Structs.WebsiteData.websiteDataUnref' when you\'re done with them. /(Can throw 'Data.GI.Base.GError.GError')/
websiteDataManagerFetchFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebsiteDataManager a,
 IsAsyncResult b) =>
a -> b -> m [WebsiteData]
websiteDataManagerFetchFinish a
manager b
result_ = IO [WebsiteData] -> m [WebsiteData]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [WebsiteData] -> m [WebsiteData])
-> IO [WebsiteData] -> m [WebsiteData]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO [WebsiteData] -> IO () -> IO [WebsiteData]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr (GList (Ptr WebsiteData))
result <- (Ptr (Ptr GError) -> IO (Ptr (GList (Ptr WebsiteData))))
-> IO (Ptr (GList (Ptr WebsiteData)))
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr (GList (Ptr WebsiteData))))
 -> IO (Ptr (GList (Ptr WebsiteData))))
-> (Ptr (Ptr GError) -> IO (Ptr (GList (Ptr WebsiteData))))
-> IO (Ptr (GList (Ptr WebsiteData)))
forall a b. (a -> b) -> a -> b
$ Ptr WebsiteDataManager
-> Ptr AsyncResult
-> Ptr (Ptr GError)
-> IO (Ptr (GList (Ptr WebsiteData)))
webkit_website_data_manager_fetch_finish Ptr WebsiteDataManager
manager' Ptr AsyncResult
result_'
        [Ptr WebsiteData]
result' <- Ptr (GList (Ptr WebsiteData)) -> IO [Ptr WebsiteData]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr WebsiteData))
result
        [WebsiteData]
result'' <- (Ptr WebsiteData -> IO WebsiteData)
-> [Ptr WebsiteData] -> IO [WebsiteData]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr WebsiteData -> WebsiteData)
-> Ptr WebsiteData -> IO WebsiteData
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr WebsiteData -> WebsiteData
WebKit.WebsiteData.WebsiteData) [Ptr WebsiteData]
result'
        Ptr (GList (Ptr WebsiteData)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr WebsiteData))
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        [WebsiteData] -> IO [WebsiteData]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [WebsiteData]
result''
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerFetchFinishMethodInfo
instance (signature ~ (b -> m [WebKit.WebsiteData.WebsiteData]), MonadIO m, IsWebsiteDataManager a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod WebsiteDataManagerFetchFinishMethodInfo a signature where
    overloadedMethod = websiteDataManagerFetchFinish

instance O.OverloadedMethodInfo WebsiteDataManagerFetchFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerFetchFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerFetchFinish"
        })


#endif

-- method WebsiteDataManager::get_base_cache_directory
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_get_base_cache_directory" webkit_website_data_manager_get_base_cache_directory :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    IO CString

-- | Get the [WebsiteDataManager:baseCacheDirectory]("GI.WebKit.Objects.WebsiteDataManager#g:attr:baseCacheDirectory") property.
-- 
-- /Since: 2.10/
websiteDataManagerGetBaseCacheDirectory ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the base directory for caches, or 'P.Nothing' if
    --    [WebsiteDataManager:baseCacheDirectory]("GI.WebKit.Objects.WebsiteDataManager#g:attr:baseCacheDirectory") was not provided or /@manager@/ is ephemeral.
websiteDataManagerGetBaseCacheDirectory :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
a -> m (Maybe Text)
websiteDataManagerGetBaseCacheDirectory a
manager = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
result <- Ptr WebsiteDataManager -> IO CString
webkit_website_data_manager_get_base_cache_directory Ptr WebsiteDataManager
manager'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerGetBaseCacheDirectoryMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsWebsiteDataManager a) => O.OverloadedMethod WebsiteDataManagerGetBaseCacheDirectoryMethodInfo a signature where
    overloadedMethod = websiteDataManagerGetBaseCacheDirectory

instance O.OverloadedMethodInfo WebsiteDataManagerGetBaseCacheDirectoryMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetBaseCacheDirectory",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerGetBaseCacheDirectory"
        })


#endif

-- method WebsiteDataManager::get_base_data_directory
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_get_base_data_directory" webkit_website_data_manager_get_base_data_directory :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    IO CString

-- | Get the [WebsiteDataManager:baseDataDirectory]("GI.WebKit.Objects.WebsiteDataManager#g:attr:baseDataDirectory") property.
-- 
-- /Since: 2.10/
websiteDataManagerGetBaseDataDirectory ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the base directory for website data, or 'P.Nothing' if
    --    [WebsiteDataManager:baseDataDirectory]("GI.WebKit.Objects.WebsiteDataManager#g:attr:baseDataDirectory") was not provided or /@manager@/ is ephemeral.
websiteDataManagerGetBaseDataDirectory :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
a -> m (Maybe Text)
websiteDataManagerGetBaseDataDirectory a
manager = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
result <- Ptr WebsiteDataManager -> IO CString
webkit_website_data_manager_get_base_data_directory Ptr WebsiteDataManager
manager'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerGetBaseDataDirectoryMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsWebsiteDataManager a) => O.OverloadedMethod WebsiteDataManagerGetBaseDataDirectoryMethodInfo a signature where
    overloadedMethod = websiteDataManagerGetBaseDataDirectory

instance O.OverloadedMethodInfo WebsiteDataManagerGetBaseDataDirectoryMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetBaseDataDirectory",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerGetBaseDataDirectory"
        })


#endif

-- method WebsiteDataManager::get_favicon_database
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "WebKit" , name = "FaviconDatabase" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_get_favicon_database" webkit_website_data_manager_get_favicon_database :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    IO (Ptr WebKit.FaviconDatabase.FaviconDatabase)

-- | Get the t'GI.WebKit.Objects.FaviconDatabase.FaviconDatabase' of /@manager@/.
-- 
-- /Since: 2.40/
websiteDataManagerGetFaviconDatabase ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> m (Maybe WebKit.FaviconDatabase.FaviconDatabase)
    -- ^ __Returns:__ a t'GI.WebKit.Objects.FaviconDatabase.FaviconDatabase', or 'P.Nothing' if website icons are disabled
websiteDataManagerGetFaviconDatabase :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
a -> m (Maybe FaviconDatabase)
websiteDataManagerGetFaviconDatabase a
manager = IO (Maybe FaviconDatabase) -> m (Maybe FaviconDatabase)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FaviconDatabase) -> m (Maybe FaviconDatabase))
-> IO (Maybe FaviconDatabase) -> m (Maybe FaviconDatabase)
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr FaviconDatabase
result <- Ptr WebsiteDataManager -> IO (Ptr FaviconDatabase)
webkit_website_data_manager_get_favicon_database Ptr WebsiteDataManager
manager'
    Maybe FaviconDatabase
maybeResult <- Ptr FaviconDatabase
-> (Ptr FaviconDatabase -> IO FaviconDatabase)
-> IO (Maybe FaviconDatabase)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FaviconDatabase
result ((Ptr FaviconDatabase -> IO FaviconDatabase)
 -> IO (Maybe FaviconDatabase))
-> (Ptr FaviconDatabase -> IO FaviconDatabase)
-> IO (Maybe FaviconDatabase)
forall a b. (a -> b) -> a -> b
$ \Ptr FaviconDatabase
result' -> do
        FaviconDatabase
result'' <- ((ManagedPtr FaviconDatabase -> FaviconDatabase)
-> Ptr FaviconDatabase -> IO FaviconDatabase
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FaviconDatabase -> FaviconDatabase
WebKit.FaviconDatabase.FaviconDatabase) Ptr FaviconDatabase
result'
        FaviconDatabase -> IO FaviconDatabase
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FaviconDatabase
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Maybe FaviconDatabase -> IO (Maybe FaviconDatabase)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FaviconDatabase
maybeResult

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerGetFaviconDatabaseMethodInfo
instance (signature ~ (m (Maybe WebKit.FaviconDatabase.FaviconDatabase)), MonadIO m, IsWebsiteDataManager a) => O.OverloadedMethod WebsiteDataManagerGetFaviconDatabaseMethodInfo a signature where
    overloadedMethod = websiteDataManagerGetFaviconDatabase

instance O.OverloadedMethodInfo WebsiteDataManagerGetFaviconDatabaseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetFaviconDatabase",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerGetFaviconDatabase"
        })


#endif

-- method WebsiteDataManager::get_favicons_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_get_favicons_enabled" webkit_website_data_manager_get_favicons_enabled :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    IO CInt

-- | Get whether website icons are enabled.
-- 
-- /Since: 2.40/
websiteDataManagerGetFaviconsEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if website icons are enabled, or 'P.False' otherwise.
websiteDataManagerGetFaviconsEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
a -> m Bool
websiteDataManagerGetFaviconsEnabled a
manager = 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 WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CInt
result <- Ptr WebsiteDataManager -> IO CInt
webkit_website_data_manager_get_favicons_enabled Ptr WebsiteDataManager
manager'
    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
manager
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerGetFaviconsEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsWebsiteDataManager a) => O.OverloadedMethod WebsiteDataManagerGetFaviconsEnabledMethodInfo a signature where
    overloadedMethod = websiteDataManagerGetFaviconsEnabled

instance O.OverloadedMethodInfo WebsiteDataManagerGetFaviconsEnabledMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetFaviconsEnabled",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerGetFaviconsEnabled"
        })


#endif

-- method WebsiteDataManager::get_itp_summary
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GAsyncReadyCallback to call when the request is satisfied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_get_itp_summary" webkit_website_data_manager_get_itp_summary :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously get the list of t'GI.WebKit.Structs.ITPThirdParty.ITPThirdParty' seen for /@manager@/.
-- 
-- Every t'GI.WebKit.Structs.ITPThirdParty.ITPThirdParty'
-- contains the list of t'GI.WebKit.Structs.ITPFirstParty.ITPFirstParty' under which it has been seen.
-- 
-- When the operation is finished, /@callback@/ will be called. You can then call
-- 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetItpSummaryFinish' to get the result of the operation.
-- 
-- /Since: 2.30/
websiteDataManagerGetItpSummary ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing' to ignore
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is satisfied
    -> m ()
websiteDataManagerGetItpSummary :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebsiteDataManager a,
 IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
websiteDataManagerGetItpSummary a
manager Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) AsyncReadyCallback
jCallback)
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr WebsiteDataManager
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
webkit_website_data_manager_get_itp_summary Ptr WebsiteDataManager
manager' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerGetItpSummaryMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsWebsiteDataManager a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod WebsiteDataManagerGetItpSummaryMethodInfo a signature where
    overloadedMethod = websiteDataManagerGetItpSummary

instance O.OverloadedMethodInfo WebsiteDataManagerGetItpSummaryMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetItpSummary",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerGetItpSummary"
        })


#endif

-- method WebsiteDataManager::get_itp_summary_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncResult" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface
--                     Name { namespace = "WebKit" , name = "ITPThirdParty" }))
-- throws : True
-- Skip return : False

foreign import ccall "webkit_website_data_manager_get_itp_summary_finish" webkit_website_data_manager_get_itp_summary_finish :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr (GList (Ptr WebKit.ITPThirdParty.ITPThirdParty)))

-- | Finish an asynchronous operation started with 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetItpSummary'.
-- 
-- /Since: 2.30/
websiteDataManagerGetItpSummaryFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'
    -> m [WebKit.ITPThirdParty.ITPThirdParty]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of t'GI.WebKit.Structs.ITPThirdParty.ITPThirdParty'.
    --    You must free the t'GI.GLib.Structs.List.List' with @/g_list_free()/@ and unref the t'GI.WebKit.Structs.ITPThirdParty.ITPThirdParty's with
    --    'GI.WebKit.Structs.ITPThirdParty.iTPThirdPartyUnref' when you\'re done with them. /(Can throw 'Data.GI.Base.GError.GError')/
websiteDataManagerGetItpSummaryFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebsiteDataManager a,
 IsAsyncResult b) =>
a -> b -> m [ITPThirdParty]
websiteDataManagerGetItpSummaryFinish a
manager b
result_ = IO [ITPThirdParty] -> m [ITPThirdParty]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ITPThirdParty] -> m [ITPThirdParty])
-> IO [ITPThirdParty] -> m [ITPThirdParty]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO [ITPThirdParty] -> IO () -> IO [ITPThirdParty]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr (GList (Ptr ITPThirdParty))
result <- (Ptr (Ptr GError) -> IO (Ptr (GList (Ptr ITPThirdParty))))
-> IO (Ptr (GList (Ptr ITPThirdParty)))
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr (GList (Ptr ITPThirdParty))))
 -> IO (Ptr (GList (Ptr ITPThirdParty))))
-> (Ptr (Ptr GError) -> IO (Ptr (GList (Ptr ITPThirdParty))))
-> IO (Ptr (GList (Ptr ITPThirdParty)))
forall a b. (a -> b) -> a -> b
$ Ptr WebsiteDataManager
-> Ptr AsyncResult
-> Ptr (Ptr GError)
-> IO (Ptr (GList (Ptr ITPThirdParty)))
webkit_website_data_manager_get_itp_summary_finish Ptr WebsiteDataManager
manager' Ptr AsyncResult
result_'
        [Ptr ITPThirdParty]
result' <- Ptr (GList (Ptr ITPThirdParty)) -> IO [Ptr ITPThirdParty]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ITPThirdParty))
result
        [ITPThirdParty]
result'' <- (Ptr ITPThirdParty -> IO ITPThirdParty)
-> [Ptr ITPThirdParty] -> IO [ITPThirdParty]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr ITPThirdParty -> ITPThirdParty)
-> Ptr ITPThirdParty -> IO ITPThirdParty
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr ITPThirdParty -> ITPThirdParty
WebKit.ITPThirdParty.ITPThirdParty) [Ptr ITPThirdParty]
result'
        Ptr (GList (Ptr ITPThirdParty)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr ITPThirdParty))
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        [ITPThirdParty] -> IO [ITPThirdParty]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ITPThirdParty]
result''
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerGetItpSummaryFinishMethodInfo
instance (signature ~ (b -> m [WebKit.ITPThirdParty.ITPThirdParty]), MonadIO m, IsWebsiteDataManager a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod WebsiteDataManagerGetItpSummaryFinishMethodInfo a signature where
    overloadedMethod = websiteDataManagerGetItpSummaryFinish

instance O.OverloadedMethodInfo WebsiteDataManagerGetItpSummaryFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetItpSummaryFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerGetItpSummaryFinish"
        })


#endif

-- method WebsiteDataManager::is_ephemeral
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_is_ephemeral" webkit_website_data_manager_is_ephemeral :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    IO CInt

-- | Get whether a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager' is ephemeral.
-- 
-- See [WebsiteDataManager:isEphemeral]("GI.WebKit.Objects.WebsiteDataManager#g:attr:isEphemeral") for more details.
-- 
-- /Since: 2.16/
websiteDataManagerIsEphemeral ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@manager@/ is ephemeral or 'P.False' otherwise.
websiteDataManagerIsEphemeral :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
a -> m Bool
websiteDataManagerIsEphemeral a
manager = 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 WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CInt
result <- Ptr WebsiteDataManager -> IO CInt
webkit_website_data_manager_is_ephemeral Ptr WebsiteDataManager
manager'
    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
manager
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerIsEphemeralMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsWebsiteDataManager a) => O.OverloadedMethod WebsiteDataManagerIsEphemeralMethodInfo a signature where
    overloadedMethod = websiteDataManagerIsEphemeral

instance O.OverloadedMethodInfo WebsiteDataManagerIsEphemeralMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerIsEphemeral",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerIsEphemeral"
        })


#endif

-- method WebsiteDataManager::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "types"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataTypes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#WebKitWebsiteDataTypes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "website_data"
--           , argType =
--               TGList
--                 (TInterface Name { namespace = "WebKit" , name = "WebsiteData" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GList of #WebKitWebsiteData"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable or %NULL to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GAsyncReadyCallback to call when the request is satisfied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_remove" webkit_website_data_manager_remove :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    CUInt ->                                -- types : TInterface (Name {namespace = "WebKit", name = "WebsiteDataTypes"})
    Ptr (GList (Ptr WebKit.WebsiteData.WebsiteData)) -> -- website_data : TGList (TInterface (Name {namespace = "WebKit", name = "WebsiteData"}))
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously removes the website data in the given /@websiteData@/ list.
-- 
-- Asynchronously removes the website data of the given /@types@/ for websites in the given /@websiteData@/ list.
-- Use 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerClear' if you want to remove the website data for all sites.
-- 
-- When the operation is finished, /@callback@/ will be called. You can then call
-- 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerRemoveFinish' to get the result of the operation.
-- 
-- /Since: 2.16/
websiteDataManagerRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> [WebKit.Flags.WebsiteDataTypes]
    -- ^ /@types@/: t'GI.WebKit.Flags.WebsiteDataTypes'
    -> [WebKit.WebsiteData.WebsiteData]
    -- ^ /@websiteData@/: a t'GI.GLib.Structs.List.List' of t'GI.WebKit.Structs.WebsiteData.WebsiteData'
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable' or 'P.Nothing' to ignore
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the request is satisfied
    -> m ()
websiteDataManagerRemove :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebsiteDataManager a,
 IsCancellable b) =>
a
-> [WebsiteDataTypes]
-> [WebsiteData]
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
websiteDataManagerRemove a
manager [WebsiteDataTypes]
types [WebsiteData]
websiteData Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    let types' :: CUInt
types' = [WebsiteDataTypes] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [WebsiteDataTypes]
types
    [Ptr WebsiteData]
websiteData' <- (WebsiteData -> IO (Ptr WebsiteData))
-> [WebsiteData] -> IO [Ptr WebsiteData]
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 WebsiteData -> IO (Ptr WebsiteData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [WebsiteData]
websiteData
    Ptr (GList (Ptr WebsiteData))
websiteData'' <- [Ptr WebsiteData] -> IO (Ptr (GList (Ptr WebsiteData)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr WebsiteData]
websiteData'
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) AsyncReadyCallback
jCallback)
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr WebsiteDataManager
-> CUInt
-> Ptr (GList (Ptr WebsiteData))
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
webkit_website_data_manager_remove Ptr WebsiteDataManager
manager' CUInt
types' Ptr (GList (Ptr WebsiteData))
websiteData'' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    (WebsiteData -> IO ()) -> [WebsiteData] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ WebsiteData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [WebsiteData]
websiteData
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Ptr (GList (Ptr WebsiteData)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr WebsiteData))
websiteData''
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerRemoveMethodInfo
instance (signature ~ ([WebKit.Flags.WebsiteDataTypes] -> [WebKit.WebsiteData.WebsiteData] -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsWebsiteDataManager a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod WebsiteDataManagerRemoveMethodInfo a signature where
    overloadedMethod = websiteDataManagerRemove

instance O.OverloadedMethodInfo WebsiteDataManagerRemoveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerRemove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerRemove"
        })


#endif

-- method WebsiteDataManager::remove_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncResult" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "webkit_website_data_manager_remove_finish" webkit_website_data_manager_remove_finish :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finish an asynchronous operation started with 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerRemove'.
-- 
-- /Since: 2.16/
websiteDataManagerRemoveFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
websiteDataManagerRemoveFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsWebsiteDataManager a,
 IsAsyncResult b) =>
a -> b -> m ()
websiteDataManagerRemoveFinish a
manager b
result_ = 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 WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr WebsiteDataManager
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
webkit_website_data_manager_remove_finish Ptr WebsiteDataManager
manager' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerRemoveFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsWebsiteDataManager a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod WebsiteDataManagerRemoveFinishMethodInfo a signature where
    overloadedMethod = websiteDataManagerRemoveFinish

instance O.OverloadedMethodInfo WebsiteDataManagerRemoveFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerRemoveFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerRemoveFinish"
        })


#endif

-- method WebsiteDataManager::set_favicons_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit" , name = "WebsiteDataManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebsiteDataManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "value to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_website_data_manager_set_favicons_enabled" webkit_website_data_manager_set_favicons_enabled :: 
    Ptr WebsiteDataManager ->               -- manager : TInterface (Name {namespace = "WebKit", name = "WebsiteDataManager"})
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()

-- | Set whether website icons are enabled. Website icons are disabled by default.
-- When website icons are disabled, the t'GI.WebKit.Objects.FaviconDatabase.FaviconDatabase' of /@manager@/ is closed and
-- its reference removed, so 'GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerGetFaviconDatabase' will
-- return 'P.Nothing'. If website icons are enabled again, a new t'GI.WebKit.Objects.FaviconDatabase.FaviconDatabase' will
-- be created.
-- 
-- /Since: 2.40/
websiteDataManagerSetFaviconsEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit.Objects.WebsiteDataManager.WebsiteDataManager'
    -> Bool
    -- ^ /@enabled@/: value to set
    -> m ()
websiteDataManagerSetFaviconsEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebsiteDataManager a) =>
a -> Bool -> m ()
websiteDataManagerSetFaviconsEnabled a
manager 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 WebsiteDataManager
manager' <- a -> IO (Ptr WebsiteDataManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    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 WebsiteDataManager -> CInt -> IO ()
webkit_website_data_manager_set_favicons_enabled Ptr WebsiteDataManager
manager' CInt
enabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WebsiteDataManagerSetFaviconsEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsWebsiteDataManager a) => O.OverloadedMethod WebsiteDataManagerSetFaviconsEnabledMethodInfo a signature where
    overloadedMethod = websiteDataManagerSetFaviconsEnabled

instance O.OverloadedMethodInfo WebsiteDataManagerSetFaviconsEnabledMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Objects.WebsiteDataManager.websiteDataManagerSetFaviconsEnabled",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Objects-WebsiteDataManager.html#v:websiteDataManagerSetFaviconsEnabled"
        })


#endif