{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.WebKit.Structs.WebsiteData
    ( 
    WebsiteData(..)                         ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveWebsiteDataMethod                ,
#endif
#if defined(ENABLE_OVERLOADING)
    WebsiteDataGetNameMethodInfo            ,
#endif
    websiteDataGetName                      ,
#if defined(ENABLE_OVERLOADING)
    WebsiteDataGetSizeMethodInfo            ,
#endif
    websiteDataGetSize                      ,
#if defined(ENABLE_OVERLOADING)
    WebsiteDataGetTypesMethodInfo           ,
#endif
    websiteDataGetTypes                     ,
#if defined(ENABLE_OVERLOADING)
    WebsiteDataRefMethodInfo                ,
#endif
    websiteDataRef                          ,
#if defined(ENABLE_OVERLOADING)
    WebsiteDataUnrefMethodInfo              ,
#endif
    websiteDataUnref                        ,
    ) 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 {-# SOURCE #-} qualified GI.WebKit.Flags as WebKit.Flags
newtype WebsiteData = WebsiteData (SP.ManagedPtr WebsiteData)
    deriving (WebsiteData -> WebsiteData -> Bool
(WebsiteData -> WebsiteData -> Bool)
-> (WebsiteData -> WebsiteData -> Bool) -> Eq WebsiteData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebsiteData -> WebsiteData -> Bool
== :: WebsiteData -> WebsiteData -> Bool
$c/= :: WebsiteData -> WebsiteData -> Bool
/= :: WebsiteData -> WebsiteData -> Bool
Eq)
instance SP.ManagedPtrNewtype WebsiteData where
    toManagedPtr :: WebsiteData -> ManagedPtr WebsiteData
toManagedPtr (WebsiteData ManagedPtr WebsiteData
p) = ManagedPtr WebsiteData
p
foreign import ccall "webkit_website_data_get_type" c_webkit_website_data_get_type :: 
    IO GType
type instance O.ParentTypes WebsiteData = '[]
instance O.HasParentTypes WebsiteData
instance B.Types.TypedObject WebsiteData where
    glibType :: IO GType
glibType = IO GType
c_webkit_website_data_get_type
instance B.Types.GBoxed WebsiteData
instance B.GValue.IsGValue (Maybe WebsiteData) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_website_data_get_type
    gvalueSet_ :: Ptr GValue -> Maybe WebsiteData -> IO ()
gvalueSet_ Ptr GValue
gv Maybe WebsiteData
P.Nothing = Ptr GValue -> Ptr WebsiteData -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr WebsiteData
forall a. Ptr a
FP.nullPtr :: FP.Ptr WebsiteData)
    gvalueSet_ Ptr GValue
gv (P.Just WebsiteData
obj) = WebsiteData -> (Ptr WebsiteData -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr WebsiteData
obj (Ptr GValue -> Ptr WebsiteData -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe WebsiteData)
gvalueGet_ Ptr GValue
gv = do
        Ptr WebsiteData
ptr <- Ptr GValue -> IO (Ptr WebsiteData)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr WebsiteData)
        if Ptr WebsiteData
ptr Ptr WebsiteData -> Ptr WebsiteData -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr WebsiteData
forall a. Ptr a
FP.nullPtr
        then WebsiteData -> Maybe WebsiteData
forall a. a -> Maybe a
P.Just (WebsiteData -> Maybe WebsiteData)
-> IO WebsiteData -> IO (Maybe WebsiteData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr WebsiteData -> WebsiteData)
-> Ptr WebsiteData -> IO WebsiteData
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr WebsiteData -> WebsiteData
WebsiteData Ptr WebsiteData
ptr
        else Maybe WebsiteData -> IO (Maybe WebsiteData)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebsiteData
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WebsiteData
type instance O.AttributeList WebsiteData = WebsiteDataAttributeList
type WebsiteDataAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "webkit_website_data_get_name" webkit_website_data_get_name :: 
    Ptr WebsiteData ->                      
    IO CString
websiteDataGetName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WebsiteData
    
    -> m T.Text
    
websiteDataGetName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
WebsiteData -> m Text
websiteDataGetName WebsiteData
websiteData = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteData
websiteData' <- WebsiteData -> IO (Ptr WebsiteData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WebsiteData
websiteData
    CString
result <- Ptr WebsiteData -> IO CString
webkit_website_data_get_name Ptr WebsiteData
websiteData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"websiteDataGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    WebsiteData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WebsiteData
websiteData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data WebsiteDataGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod WebsiteDataGetNameMethodInfo WebsiteData signature where
    overloadedMethod = websiteDataGetName
instance O.OverloadedMethodInfo WebsiteDataGetNameMethodInfo WebsiteData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Structs.WebsiteData.websiteDataGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Structs-WebsiteData.html#v:websiteDataGetName"
        })
#endif
foreign import ccall "webkit_website_data_get_size" webkit_website_data_get_size :: 
    Ptr WebsiteData ->                      
    CUInt ->                                
    IO Word64
websiteDataGetSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WebsiteData
    
    -> [WebKit.Flags.WebsiteDataTypes]
    
    -> m Word64
    
websiteDataGetSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
WebsiteData -> [WebsiteDataTypes] -> m Word64
websiteDataGetSize WebsiteData
websiteData [WebsiteDataTypes]
types = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteData
websiteData' <- WebsiteData -> IO (Ptr WebsiteData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WebsiteData
websiteData
    let types' :: CUInt
types' = [WebsiteDataTypes] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [WebsiteDataTypes]
types
    Word64
result <- Ptr WebsiteData -> CUInt -> IO Word64
webkit_website_data_get_size Ptr WebsiteData
websiteData' CUInt
types'
    WebsiteData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WebsiteData
websiteData
    Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result
#if defined(ENABLE_OVERLOADING)
data WebsiteDataGetSizeMethodInfo
instance (signature ~ ([WebKit.Flags.WebsiteDataTypes] -> m Word64), MonadIO m) => O.OverloadedMethod WebsiteDataGetSizeMethodInfo WebsiteData signature where
    overloadedMethod = websiteDataGetSize
instance O.OverloadedMethodInfo WebsiteDataGetSizeMethodInfo WebsiteData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Structs.WebsiteData.websiteDataGetSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Structs-WebsiteData.html#v:websiteDataGetSize"
        })
#endif
foreign import ccall "webkit_website_data_get_types" webkit_website_data_get_types :: 
    Ptr WebsiteData ->                      
    IO CUInt
websiteDataGetTypes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WebsiteData
    
    -> m [WebKit.Flags.WebsiteDataTypes]
    
websiteDataGetTypes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
WebsiteData -> m [WebsiteDataTypes]
websiteDataGetTypes WebsiteData
websiteData = IO [WebsiteDataTypes] -> m [WebsiteDataTypes]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [WebsiteDataTypes] -> m [WebsiteDataTypes])
-> IO [WebsiteDataTypes] -> m [WebsiteDataTypes]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebsiteData
websiteData' <- WebsiteData -> IO (Ptr WebsiteData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WebsiteData
websiteData
    CUInt
result <- Ptr WebsiteData -> IO CUInt
webkit_website_data_get_types Ptr WebsiteData
websiteData'
    let result' :: [WebsiteDataTypes]
result' = CUInt -> [WebsiteDataTypes]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    WebsiteData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WebsiteData
websiteData
    [WebsiteDataTypes] -> IO [WebsiteDataTypes]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [WebsiteDataTypes]
result'
#if defined(ENABLE_OVERLOADING)
data WebsiteDataGetTypesMethodInfo
instance (signature ~ (m [WebKit.Flags.WebsiteDataTypes]), MonadIO m) => O.OverloadedMethod WebsiteDataGetTypesMethodInfo WebsiteData signature where
    overloadedMethod = websiteDataGetTypes
instance O.OverloadedMethodInfo WebsiteDataGetTypesMethodInfo WebsiteData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Structs.WebsiteData.websiteDataGetTypes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Structs-WebsiteData.html#v:websiteDataGetTypes"
        })
#endif
foreign import ccall "webkit_website_data_ref" webkit_website_data_ref :: 
    Ptr WebsiteData ->                      
    IO (Ptr WebsiteData)
websiteDataRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WebsiteData
    
    -> m WebsiteData
    
websiteDataRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
WebsiteData -> m WebsiteData
websiteDataRef WebsiteData
websiteData = 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 WebsiteData
websiteData' <- WebsiteData -> IO (Ptr WebsiteData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WebsiteData
websiteData
    Ptr WebsiteData
result <- Ptr WebsiteData -> IO (Ptr WebsiteData)
webkit_website_data_ref Ptr WebsiteData
websiteData'
    Text -> Ptr WebsiteData -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"websiteDataRef" Ptr WebsiteData
result
    WebsiteData
result' <- ((ManagedPtr WebsiteData -> WebsiteData)
-> Ptr WebsiteData -> IO WebsiteData
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr WebsiteData -> WebsiteData
WebsiteData) Ptr WebsiteData
result
    WebsiteData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WebsiteData
websiteData
    WebsiteData -> IO WebsiteData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WebsiteData
result'
#if defined(ENABLE_OVERLOADING)
data WebsiteDataRefMethodInfo
instance (signature ~ (m WebsiteData), MonadIO m) => O.OverloadedMethod WebsiteDataRefMethodInfo WebsiteData signature where
    overloadedMethod = websiteDataRef
instance O.OverloadedMethodInfo WebsiteDataRefMethodInfo WebsiteData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Structs.WebsiteData.websiteDataRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Structs-WebsiteData.html#v:websiteDataRef"
        })
#endif
foreign import ccall "webkit_website_data_unref" webkit_website_data_unref :: 
    Ptr WebsiteData ->                      
    IO ()
websiteDataUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WebsiteData
    
    -> m ()
websiteDataUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
WebsiteData -> m ()
websiteDataUnref WebsiteData
websiteData = 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 WebsiteData
websiteData' <- WebsiteData -> IO (Ptr WebsiteData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WebsiteData
websiteData
    Ptr WebsiteData -> IO ()
webkit_website_data_unref Ptr WebsiteData
websiteData'
    WebsiteData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WebsiteData
websiteData
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WebsiteDataUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod WebsiteDataUnrefMethodInfo WebsiteData signature where
    overloadedMethod = websiteDataUnref
instance O.OverloadedMethodInfo WebsiteDataUnrefMethodInfo WebsiteData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit.Structs.WebsiteData.websiteDataUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.2/docs/GI-WebKit-Structs-WebsiteData.html#v:websiteDataUnref"
        })
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveWebsiteDataMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveWebsiteDataMethod "ref" o = WebsiteDataRefMethodInfo
    ResolveWebsiteDataMethod "unref" o = WebsiteDataUnrefMethodInfo
    ResolveWebsiteDataMethod "getName" o = WebsiteDataGetNameMethodInfo
    ResolveWebsiteDataMethod "getSize" o = WebsiteDataGetSizeMethodInfo
    ResolveWebsiteDataMethod "getTypes" o = WebsiteDataGetTypesMethodInfo
    ResolveWebsiteDataMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveWebsiteDataMethod t WebsiteData, O.OverloadedMethod info WebsiteData p) => OL.IsLabel t (WebsiteData -> 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 ~ ResolveWebsiteDataMethod t WebsiteData, O.OverloadedMethod info WebsiteData p, R.HasField t WebsiteData p) => R.HasField t WebsiteData p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveWebsiteDataMethod t WebsiteData, O.OverloadedMethodInfo info WebsiteData) => OL.IsLabel t (O.MethodProxy info WebsiteData) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif