{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Soup.Objects.CookieJarDB
    ( 
    CookieJarDB(..)                         ,
    IsCookieJarDB                           ,
    toCookieJarDB                           ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveCookieJarDBMethod                ,
#endif
    cookieJarDBNew                          ,
 
#if defined(ENABLE_OVERLOADING)
    CookieJarDBFilenamePropertyInfo         ,
#endif
    constructCookieJarDBFilename            ,
#if defined(ENABLE_OVERLOADING)
    cookieJarDBFilename                     ,
#endif
    getCookieJarDBFilename                  ,
    ) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Soup.Interfaces.SessionFeature as Soup.SessionFeature
import {-# SOURCE #-} qualified GI.Soup.Objects.CookieJar as Soup.CookieJar
newtype CookieJarDB = CookieJarDB (SP.ManagedPtr CookieJarDB)
    deriving (CookieJarDB -> CookieJarDB -> Bool
(CookieJarDB -> CookieJarDB -> Bool)
-> (CookieJarDB -> CookieJarDB -> Bool) -> Eq CookieJarDB
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CookieJarDB -> CookieJarDB -> Bool
$c/= :: CookieJarDB -> CookieJarDB -> Bool
== :: CookieJarDB -> CookieJarDB -> Bool
$c== :: CookieJarDB -> CookieJarDB -> Bool
Eq)
instance SP.ManagedPtrNewtype CookieJarDB where
    toManagedPtr :: CookieJarDB -> ManagedPtr CookieJarDB
toManagedPtr (CookieJarDB ManagedPtr CookieJarDB
p) = ManagedPtr CookieJarDB
p
foreign import ccall "soup_cookie_jar_db_get_type"
    c_soup_cookie_jar_db_get_type :: IO B.Types.GType
instance B.Types.TypedObject CookieJarDB where
    glibType :: IO GType
glibType = IO GType
c_soup_cookie_jar_db_get_type
instance B.Types.GObject CookieJarDB
instance B.GValue.IsGValue CookieJarDB where
    toGValue :: CookieJarDB -> IO GValue
toGValue CookieJarDB
o = do
        GType
gtype <- IO GType
c_soup_cookie_jar_db_get_type
        CookieJarDB -> (Ptr CookieJarDB -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CookieJarDB
o (GType
-> (GValue -> Ptr CookieJarDB -> IO ())
-> Ptr CookieJarDB
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr CookieJarDB -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO CookieJarDB
fromGValue GValue
gv = do
        Ptr CookieJarDB
ptr <- GValue -> IO (Ptr CookieJarDB)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr CookieJarDB)
        (ManagedPtr CookieJarDB -> CookieJarDB)
-> Ptr CookieJarDB -> IO CookieJarDB
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr CookieJarDB -> CookieJarDB
CookieJarDB Ptr CookieJarDB
ptr
        
    
class (SP.GObject o, O.IsDescendantOf CookieJarDB o) => IsCookieJarDB o
instance (SP.GObject o, O.IsDescendantOf CookieJarDB o) => IsCookieJarDB o
instance O.HasParentTypes CookieJarDB
type instance O.ParentTypes CookieJarDB = '[Soup.CookieJar.CookieJar, GObject.Object.Object, Soup.SessionFeature.SessionFeature]
toCookieJarDB :: (MonadIO m, IsCookieJarDB o) => o -> m CookieJarDB
toCookieJarDB :: o -> m CookieJarDB
toCookieJarDB = IO CookieJarDB -> m CookieJarDB
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CookieJarDB -> m CookieJarDB)
-> (o -> IO CookieJarDB) -> o -> m CookieJarDB
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr CookieJarDB -> CookieJarDB) -> o -> IO CookieJarDB
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr CookieJarDB -> CookieJarDB
CookieJarDB
#if defined(ENABLE_OVERLOADING)
type family ResolveCookieJarDBMethod (t :: Symbol) (o :: *) :: * where
    ResolveCookieJarDBMethod "addCookie" o = Soup.CookieJar.CookieJarAddCookieMethodInfo
    ResolveCookieJarDBMethod "addCookieFull" o = Soup.CookieJar.CookieJarAddCookieFullMethodInfo
    ResolveCookieJarDBMethod "addCookieWithFirstParty" o = Soup.CookieJar.CookieJarAddCookieWithFirstPartyMethodInfo
    ResolveCookieJarDBMethod "addFeature" o = Soup.SessionFeature.SessionFeatureAddFeatureMethodInfo
    ResolveCookieJarDBMethod "allCookies" o = Soup.CookieJar.CookieJarAllCookiesMethodInfo
    ResolveCookieJarDBMethod "attach" o = Soup.SessionFeature.SessionFeatureAttachMethodInfo
    ResolveCookieJarDBMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCookieJarDBMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCookieJarDBMethod "deleteCookie" o = Soup.CookieJar.CookieJarDeleteCookieMethodInfo
    ResolveCookieJarDBMethod "detach" o = Soup.SessionFeature.SessionFeatureDetachMethodInfo
    ResolveCookieJarDBMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCookieJarDBMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCookieJarDBMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCookieJarDBMethod "hasFeature" o = Soup.SessionFeature.SessionFeatureHasFeatureMethodInfo
    ResolveCookieJarDBMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCookieJarDBMethod "isPersistent" o = Soup.CookieJar.CookieJarIsPersistentMethodInfo
    ResolveCookieJarDBMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCookieJarDBMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCookieJarDBMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCookieJarDBMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCookieJarDBMethod "removeFeature" o = Soup.SessionFeature.SessionFeatureRemoveFeatureMethodInfo
    ResolveCookieJarDBMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCookieJarDBMethod "save" o = Soup.CookieJar.CookieJarSaveMethodInfo
    ResolveCookieJarDBMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCookieJarDBMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCookieJarDBMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCookieJarDBMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCookieJarDBMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCookieJarDBMethod "getAcceptPolicy" o = Soup.CookieJar.CookieJarGetAcceptPolicyMethodInfo
    ResolveCookieJarDBMethod "getCookieList" o = Soup.CookieJar.CookieJarGetCookieListMethodInfo
    ResolveCookieJarDBMethod "getCookieListWithSameSiteInfo" o = Soup.CookieJar.CookieJarGetCookieListWithSameSiteInfoMethodInfo
    ResolveCookieJarDBMethod "getCookies" o = Soup.CookieJar.CookieJarGetCookiesMethodInfo
    ResolveCookieJarDBMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCookieJarDBMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCookieJarDBMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCookieJarDBMethod "setAcceptPolicy" o = Soup.CookieJar.CookieJarSetAcceptPolicyMethodInfo
    ResolveCookieJarDBMethod "setCookie" o = Soup.CookieJar.CookieJarSetCookieMethodInfo
    ResolveCookieJarDBMethod "setCookieWithFirstParty" o = Soup.CookieJar.CookieJarSetCookieWithFirstPartyMethodInfo
    ResolveCookieJarDBMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCookieJarDBMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCookieJarDBMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCookieJarDBMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveCookieJarDBMethod t CookieJarDB, O.MethodInfo info CookieJarDB p) => OL.IsLabel t (CookieJarDB -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#endif
   
   
   
getCookieJarDBFilename :: (MonadIO m, IsCookieJarDB o) => o -> m (Maybe T.Text)
getCookieJarDBFilename :: o -> m (Maybe Text)
getCookieJarDBFilename o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"filename"
constructCookieJarDBFilename :: (IsCookieJarDB o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructCookieJarDBFilename :: Text -> m (GValueConstruct o)
constructCookieJarDBFilename Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"filename" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data CookieJarDBFilenamePropertyInfo
instance AttrInfo CookieJarDBFilenamePropertyInfo where
    type AttrAllowedOps CookieJarDBFilenamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CookieJarDBFilenamePropertyInfo = IsCookieJarDB
    type AttrSetTypeConstraint CookieJarDBFilenamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CookieJarDBFilenamePropertyInfo = (~) T.Text
    type AttrTransferType CookieJarDBFilenamePropertyInfo = T.Text
    type AttrGetType CookieJarDBFilenamePropertyInfo = (Maybe T.Text)
    type AttrLabel CookieJarDBFilenamePropertyInfo = "filename"
    type AttrOrigin CookieJarDBFilenamePropertyInfo = CookieJarDB
    attrGet = getCookieJarDBFilename
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructCookieJarDBFilename
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CookieJarDB
type instance O.AttributeList CookieJarDB = CookieJarDBAttributeList
type CookieJarDBAttributeList = ('[ '("acceptPolicy", Soup.CookieJar.CookieJarAcceptPolicyPropertyInfo), '("filename", CookieJarDBFilenamePropertyInfo), '("readOnly", Soup.CookieJar.CookieJarReadOnlyPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
cookieJarDBFilename :: AttrLabelProxy "filename"
cookieJarDBFilename = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CookieJarDB = CookieJarDBSignalList
type CookieJarDBSignalList = ('[ '("changed", Soup.CookieJar.CookieJarChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "soup_cookie_jar_db_new" soup_cookie_jar_db_new :: 
    CString ->                              
    CInt ->                                 
    IO (Ptr CookieJarDB)
cookieJarDBNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    -> Bool
    
    -> m CookieJarDB
    
cookieJarDBNew :: Text -> Bool -> m CookieJarDB
cookieJarDBNew Text
filename Bool
readOnly = IO CookieJarDB -> m CookieJarDB
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CookieJarDB -> m CookieJarDB)
-> IO CookieJarDB -> m CookieJarDB
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- Text -> IO CString
textToCString Text
filename
    let readOnly' :: CInt
readOnly' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
readOnly
    Ptr CookieJarDB
result <- CString -> CInt -> IO (Ptr CookieJarDB)
soup_cookie_jar_db_new CString
filename' CInt
readOnly'
    Text -> Ptr CookieJarDB -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cookieJarDBNew" Ptr CookieJarDB
result
    CookieJarDB
result' <- ((ManagedPtr CookieJarDB -> CookieJarDB)
-> Ptr CookieJarDB -> IO CookieJarDB
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr CookieJarDB -> CookieJarDB
CookieJarDB) Ptr CookieJarDB
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    CookieJarDB -> IO CookieJarDB
forall (m :: * -> *) a. Monad m => a -> m a
return CookieJarDB
result'
#if defined(ENABLE_OVERLOADING)
#endif