{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.WebKit2WebExtension.Objects.DOMFile
    ( 

-- * Exported types
    DOMFile(..)                             ,
    IsDOMFile                               ,
    toDOMFile                               ,


 -- * 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"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [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"), [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
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getName]("GI.WebKit2WebExtension.Objects.DOMFile#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSize]("GI.WebKit2WebExtension.Objects.DOMBlob#g:method:getSize").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMFileMethod                    ,
#endif

-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    DOMFileGetNameMethodInfo                ,
#endif
    dOMFileGetName                          ,




 -- * Properties


-- ** name #attr:name#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMFileNamePropertyInfo                 ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMFileName                             ,
#endif
    getDOMFileName                          ,




    ) 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.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.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 {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMBlob as WebKit2WebExtension.DOMBlob
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject

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

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

foreign import ccall "webkit_dom_file_get_type"
    c_webkit_dom_file_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMFile where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_file_get_type

instance B.Types.GObject DOMFile

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

instance O.HasParentTypes DOMFile
type instance O.ParentTypes DOMFile = '[WebKit2WebExtension.DOMBlob.DOMBlob, WebKit2WebExtension.DOMObject.DOMObject, GObject.Object.Object]

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

-- | Convert 'DOMFile' 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 DOMFile) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_dom_file_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DOMFile -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DOMFile
P.Nothing = Ptr GValue -> Ptr DOMFile -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DOMFile
forall a. Ptr a
FP.nullPtr :: FP.Ptr DOMFile)
    gvalueSet_ Ptr GValue
gv (P.Just DOMFile
obj) = DOMFile -> (Ptr DOMFile -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMFile
obj (Ptr GValue -> Ptr DOMFile -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DOMFile)
gvalueGet_ Ptr GValue
gv = do
        Ptr DOMFile
ptr <- Ptr GValue -> IO (Ptr DOMFile)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DOMFile)
        if Ptr DOMFile
ptr Ptr DOMFile -> Ptr DOMFile -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DOMFile
forall a. Ptr a
FP.nullPtr
        then DOMFile -> Maybe DOMFile
forall a. a -> Maybe a
P.Just (DOMFile -> Maybe DOMFile) -> IO DOMFile -> IO (Maybe DOMFile)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DOMFile -> DOMFile) -> Ptr DOMFile -> IO DOMFile
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMFile -> DOMFile
DOMFile Ptr DOMFile
ptr
        else Maybe DOMFile -> IO (Maybe DOMFile)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DOMFile
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMFileMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMFileMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMFileMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMFileMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMFileMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMFileMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMFileMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMFileMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMFileMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMFileMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMFileMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMFileMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMFileMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMFileMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMFileMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMFileMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMFileMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMFileMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMFileMethod "getName" o = DOMFileGetNameMethodInfo
    ResolveDOMFileMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMFileMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMFileMethod "getSize" o = WebKit2WebExtension.DOMBlob.DOMBlobGetSizeMethodInfo
    ResolveDOMFileMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMFileMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMFileMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMFileMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMFile #name
-- @
getDOMFileName :: (MonadIO m, IsDOMFile o) => o -> m (Maybe T.Text)
getDOMFileName :: forall (m :: * -> *) o.
(MonadIO m, IsDOMFile o) =>
o -> m (Maybe Text)
getDOMFileName o
obj = IO (Maybe Text) -> m (Maybe Text)
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
"name"

#if defined(ENABLE_OVERLOADING)
data DOMFileNamePropertyInfo
instance AttrInfo DOMFileNamePropertyInfo where
    type AttrAllowedOps DOMFileNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMFileNamePropertyInfo = IsDOMFile
    type AttrSetTypeConstraint DOMFileNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMFileNamePropertyInfo = (~) ()
    type AttrTransferType DOMFileNamePropertyInfo = ()
    type AttrGetType DOMFileNamePropertyInfo = (Maybe T.Text)
    type AttrLabel DOMFileNamePropertyInfo = "name"
    type AttrOrigin DOMFileNamePropertyInfo = DOMFile
    attrGet = getDOMFileName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMFile.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMFile.html#g:attr:name"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMFile
type instance O.AttributeList DOMFile = DOMFileAttributeList
type DOMFileAttributeList = ('[ '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("name", DOMFileNamePropertyInfo), '("size", WebKit2WebExtension.DOMBlob.DOMBlobSizePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMFileName :: AttrLabelProxy "name"
dOMFileName = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DOMFile = DOMFileSignalList
type DOMFileSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method DOMFile::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMFile" , 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_dom_file_get_name" webkit_dom_file_get_name :: 
    Ptr DOMFile ->                          -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMFile"})
    IO CString

{-# DEPRECATED dOMFileGetName ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMFileGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMFile a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMFile.DOMFile'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMFileGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMFile a) =>
a -> m Text
dOMFileGetName a
self = IO Text -> m Text
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 DOMFile
self' <- a -> IO (Ptr DOMFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMFile -> IO CString
webkit_dom_file_get_name Ptr DOMFile
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMFileGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DOMFileGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMFile a) => O.OverloadedMethod DOMFileGetNameMethodInfo a signature where
    overloadedMethod = dOMFileGetName

instance O.OverloadedMethodInfo DOMFileGetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMFile.dOMFileGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMFile.html#v:dOMFileGetName"
        })


#endif