{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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.DOMHTMLDocument
    ( 

-- * Exported types
    DOMHTMLDocument(..)                     ,
    IsDOMHTMLDocument                       ,
    toDOMHTMLDocument                       ,
    noDOMHTMLDocument                       ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDOMHTMLDocumentMethod            ,
#endif


-- ** captureEvents #method:captureEvents#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentCaptureEventsMethodInfo  ,
#endif
    dOMHTMLDocumentCaptureEvents            ,


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentClearMethodInfo          ,
#endif
    dOMHTMLDocumentClear                    ,


-- ** close #method:close#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentCloseMethodInfo          ,
#endif
    dOMHTMLDocumentClose                    ,


-- ** getAlinkColor #method:getAlinkColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetAlinkColorMethodInfo  ,
#endif
    dOMHTMLDocumentGetAlinkColor            ,


-- ** getBgColor #method:getBgColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetBgColorMethodInfo     ,
#endif
    dOMHTMLDocumentGetBgColor               ,


-- ** getCompatMode #method:getCompatMode#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetCompatModeMethodInfo  ,
#endif
    dOMHTMLDocumentGetCompatMode            ,


-- ** getDesignMode #method:getDesignMode#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetDesignModeMethodInfo  ,
#endif
    dOMHTMLDocumentGetDesignMode            ,


-- ** getDir #method:getDir#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetDirMethodInfo         ,
#endif
    dOMHTMLDocumentGetDir                   ,


-- ** getEmbeds #method:getEmbeds#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetEmbedsMethodInfo      ,
#endif
    dOMHTMLDocumentGetEmbeds                ,


-- ** getFgColor #method:getFgColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetFgColorMethodInfo     ,
#endif
    dOMHTMLDocumentGetFgColor               ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetHeightMethodInfo      ,
#endif
    dOMHTMLDocumentGetHeight                ,


-- ** getLinkColor #method:getLinkColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetLinkColorMethodInfo   ,
#endif
    dOMHTMLDocumentGetLinkColor             ,


-- ** getPlugins #method:getPlugins#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetPluginsMethodInfo     ,
#endif
    dOMHTMLDocumentGetPlugins               ,


-- ** getScripts #method:getScripts#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetScriptsMethodInfo     ,
#endif
    dOMHTMLDocumentGetScripts               ,


-- ** getVlinkColor #method:getVlinkColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetVlinkColorMethodInfo  ,
#endif
    dOMHTMLDocumentGetVlinkColor            ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentGetWidthMethodInfo       ,
#endif
    dOMHTMLDocumentGetWidth                 ,


-- ** releaseEvents #method:releaseEvents#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentReleaseEventsMethodInfo  ,
#endif
    dOMHTMLDocumentReleaseEvents            ,


-- ** setAlinkColor #method:setAlinkColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentSetAlinkColorMethodInfo  ,
#endif
    dOMHTMLDocumentSetAlinkColor            ,


-- ** setBgColor #method:setBgColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentSetBgColorMethodInfo     ,
#endif
    dOMHTMLDocumentSetBgColor               ,


-- ** setDesignMode #method:setDesignMode#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentSetDesignModeMethodInfo  ,
#endif
    dOMHTMLDocumentSetDesignMode            ,


-- ** setDir #method:setDir#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentSetDirMethodInfo         ,
#endif
    dOMHTMLDocumentSetDir                   ,


-- ** setFgColor #method:setFgColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentSetFgColorMethodInfo     ,
#endif
    dOMHTMLDocumentSetFgColor               ,


-- ** setLinkColor #method:setLinkColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentSetLinkColorMethodInfo   ,
#endif
    dOMHTMLDocumentSetLinkColor             ,


-- ** setVlinkColor #method:setVlinkColor#

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentSetVlinkColorMethodInfo  ,
#endif
    dOMHTMLDocumentSetVlinkColor            ,




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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentAlinkColorPropertyInfo   ,
#endif
    constructDOMHTMLDocumentAlinkColor      ,
#if defined(ENABLE_OVERLOADING)
    dOMHTMLDocumentAlinkColor               ,
#endif
    getDOMHTMLDocumentAlinkColor            ,
    setDOMHTMLDocumentAlinkColor            ,


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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentBgColorPropertyInfo      ,
#endif
    constructDOMHTMLDocumentBgColor         ,
#if defined(ENABLE_OVERLOADING)
    dOMHTMLDocumentBgColor                  ,
#endif
    getDOMHTMLDocumentBgColor               ,
    setDOMHTMLDocumentBgColor               ,


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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentDirPropertyInfo          ,
#endif
    constructDOMHTMLDocumentDir             ,
#if defined(ENABLE_OVERLOADING)
    dOMHTMLDocumentDir                      ,
#endif
    getDOMHTMLDocumentDir                   ,
    setDOMHTMLDocumentDir                   ,


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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentFgColorPropertyInfo      ,
#endif
    constructDOMHTMLDocumentFgColor         ,
#if defined(ENABLE_OVERLOADING)
    dOMHTMLDocumentFgColor                  ,
#endif
    getDOMHTMLDocumentFgColor               ,
    setDOMHTMLDocumentFgColor               ,


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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentHeightPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMHTMLDocumentHeight                   ,
#endif
    getDOMHTMLDocumentHeight                ,


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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentLinkColorPropertyInfo    ,
#endif
    constructDOMHTMLDocumentLinkColor       ,
#if defined(ENABLE_OVERLOADING)
    dOMHTMLDocumentLinkColor                ,
#endif
    getDOMHTMLDocumentLinkColor             ,
    setDOMHTMLDocumentLinkColor             ,


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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentVlinkColorPropertyInfo   ,
#endif
    constructDOMHTMLDocumentVlinkColor      ,
#if defined(ENABLE_OVERLOADING)
    dOMHTMLDocumentVlinkColor               ,
#endif
    getDOMHTMLDocumentVlinkColor            ,
    setDOMHTMLDocumentVlinkColor            ,


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

#if defined(ENABLE_OVERLOADING)
    DOMHTMLDocumentWidthPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMHTMLDocumentWidth                    ,
#endif
    getDOMHTMLDocumentWidth                 ,




    ) 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.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 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.WebKit2WebExtension.Interfaces.DOMEventTarget as WebKit2WebExtension.DOMEventTarget
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocument as WebKit2WebExtension.DOMDocument
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLCollection as WebKit2WebExtension.DOMHTMLCollection
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNode as WebKit2WebExtension.DOMNode
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject

-- | Memory-managed wrapper type.
newtype DOMHTMLDocument = DOMHTMLDocument (ManagedPtr DOMHTMLDocument)
    deriving (DOMHTMLDocument -> DOMHTMLDocument -> Bool
(DOMHTMLDocument -> DOMHTMLDocument -> Bool)
-> (DOMHTMLDocument -> DOMHTMLDocument -> Bool)
-> Eq DOMHTMLDocument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DOMHTMLDocument -> DOMHTMLDocument -> Bool
$c/= :: DOMHTMLDocument -> DOMHTMLDocument -> Bool
== :: DOMHTMLDocument -> DOMHTMLDocument -> Bool
$c== :: DOMHTMLDocument -> DOMHTMLDocument -> Bool
Eq)
foreign import ccall "webkit_dom_html_document_get_type"
    c_webkit_dom_html_document_get_type :: IO GType

instance GObject DOMHTMLDocument where
    gobjectType :: IO GType
gobjectType = IO GType
c_webkit_dom_html_document_get_type
    

-- | Convert 'DOMHTMLDocument' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DOMHTMLDocument where
    toGValue :: DOMHTMLDocument -> IO GValue
toGValue o :: DOMHTMLDocument
o = do
        GType
gtype <- IO GType
c_webkit_dom_html_document_get_type
        DOMHTMLDocument -> (Ptr DOMHTMLDocument -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMHTMLDocument
o (GType
-> (GValue -> Ptr DOMHTMLDocument -> IO ())
-> Ptr DOMHTMLDocument
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DOMHTMLDocument -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DOMHTMLDocument
fromGValue gv :: GValue
gv = do
        Ptr DOMHTMLDocument
ptr <- GValue -> IO (Ptr DOMHTMLDocument)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DOMHTMLDocument)
        (ManagedPtr DOMHTMLDocument -> DOMHTMLDocument)
-> Ptr DOMHTMLDocument -> IO DOMHTMLDocument
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMHTMLDocument -> DOMHTMLDocument
DOMHTMLDocument Ptr DOMHTMLDocument
ptr
        
    

-- | Type class for types which can be safely cast to `DOMHTMLDocument`, for instance with `toDOMHTMLDocument`.
class (GObject o, O.IsDescendantOf DOMHTMLDocument o) => IsDOMHTMLDocument o
instance (GObject o, O.IsDescendantOf DOMHTMLDocument o) => IsDOMHTMLDocument o

instance O.HasParentTypes DOMHTMLDocument
type instance O.ParentTypes DOMHTMLDocument = '[WebKit2WebExtension.DOMDocument.DOMDocument, WebKit2WebExtension.DOMNode.DOMNode, WebKit2WebExtension.DOMObject.DOMObject, GObject.Object.Object, WebKit2WebExtension.DOMEventTarget.DOMEventTarget]

-- | Cast to `DOMHTMLDocument`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDOMHTMLDocument :: (MonadIO m, IsDOMHTMLDocument o) => o -> m DOMHTMLDocument
toDOMHTMLDocument :: o -> m DOMHTMLDocument
toDOMHTMLDocument = IO DOMHTMLDocument -> m DOMHTMLDocument
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMHTMLDocument -> m DOMHTMLDocument)
-> (o -> IO DOMHTMLDocument) -> o -> m DOMHTMLDocument
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DOMHTMLDocument -> DOMHTMLDocument)
-> o -> IO DOMHTMLDocument
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DOMHTMLDocument -> DOMHTMLDocument
DOMHTMLDocument

-- | A convenience alias for `Nothing` :: `Maybe` `DOMHTMLDocument`.
noDOMHTMLDocument :: Maybe DOMHTMLDocument
noDOMHTMLDocument :: Maybe DOMHTMLDocument
noDOMHTMLDocument = Maybe DOMHTMLDocument
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMHTMLDocumentMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMHTMLDocumentMethod "addEventListener" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetAddEventListenerMethodInfo
    ResolveDOMHTMLDocumentMethod "adoptNode" o = WebKit2WebExtension.DOMDocument.DOMDocumentAdoptNodeMethodInfo
    ResolveDOMHTMLDocumentMethod "appendChild" o = WebKit2WebExtension.DOMNode.DOMNodeAppendChildMethodInfo
    ResolveDOMHTMLDocumentMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMHTMLDocumentMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMHTMLDocumentMethod "captureEvents" o = DOMHTMLDocumentCaptureEventsMethodInfo
    ResolveDOMHTMLDocumentMethod "caretRangeFromPoint" o = WebKit2WebExtension.DOMDocument.DOMDocumentCaretRangeFromPointMethodInfo
    ResolveDOMHTMLDocumentMethod "clear" o = DOMHTMLDocumentClearMethodInfo
    ResolveDOMHTMLDocumentMethod "cloneNodeWithError" o = WebKit2WebExtension.DOMNode.DOMNodeCloneNodeWithErrorMethodInfo
    ResolveDOMHTMLDocumentMethod "close" o = DOMHTMLDocumentCloseMethodInfo
    ResolveDOMHTMLDocumentMethod "compareDocumentPosition" o = WebKit2WebExtension.DOMNode.DOMNodeCompareDocumentPositionMethodInfo
    ResolveDOMHTMLDocumentMethod "contains" o = WebKit2WebExtension.DOMNode.DOMNodeContainsMethodInfo
    ResolveDOMHTMLDocumentMethod "createAttribute" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateAttributeMethodInfo
    ResolveDOMHTMLDocumentMethod "createAttributeNs" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateAttributeNsMethodInfo
    ResolveDOMHTMLDocumentMethod "createCdataSection" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateCdataSectionMethodInfo
    ResolveDOMHTMLDocumentMethod "createComment" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateCommentMethodInfo
    ResolveDOMHTMLDocumentMethod "createCssStyleDeclaration" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateCssStyleDeclarationMethodInfo
    ResolveDOMHTMLDocumentMethod "createDocumentFragment" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateDocumentFragmentMethodInfo
    ResolveDOMHTMLDocumentMethod "createElement" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateElementMethodInfo
    ResolveDOMHTMLDocumentMethod "createElementNs" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateElementNsMethodInfo
    ResolveDOMHTMLDocumentMethod "createEntityReference" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateEntityReferenceMethodInfo
    ResolveDOMHTMLDocumentMethod "createEvent" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateEventMethodInfo
    ResolveDOMHTMLDocumentMethod "createExpression" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateExpressionMethodInfo
    ResolveDOMHTMLDocumentMethod "createNodeIterator" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateNodeIteratorMethodInfo
    ResolveDOMHTMLDocumentMethod "createNsResolver" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateNsResolverMethodInfo
    ResolveDOMHTMLDocumentMethod "createProcessingInstruction" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateProcessingInstructionMethodInfo
    ResolveDOMHTMLDocumentMethod "createRange" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateRangeMethodInfo
    ResolveDOMHTMLDocumentMethod "createTextNode" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateTextNodeMethodInfo
    ResolveDOMHTMLDocumentMethod "createTreeWalker" o = WebKit2WebExtension.DOMDocument.DOMDocumentCreateTreeWalkerMethodInfo
    ResolveDOMHTMLDocumentMethod "dispatchEvent" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetDispatchEventMethodInfo
    ResolveDOMHTMLDocumentMethod "elementFromPoint" o = WebKit2WebExtension.DOMDocument.DOMDocumentElementFromPointMethodInfo
    ResolveDOMHTMLDocumentMethod "evaluate" o = WebKit2WebExtension.DOMDocument.DOMDocumentEvaluateMethodInfo
    ResolveDOMHTMLDocumentMethod "execCommand" o = WebKit2WebExtension.DOMDocument.DOMDocumentExecCommandMethodInfo
    ResolveDOMHTMLDocumentMethod "exitPointerLock" o = WebKit2WebExtension.DOMDocument.DOMDocumentExitPointerLockMethodInfo
    ResolveDOMHTMLDocumentMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMHTMLDocumentMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMHTMLDocumentMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMHTMLDocumentMethod "hasChildNodes" o = WebKit2WebExtension.DOMNode.DOMNodeHasChildNodesMethodInfo
    ResolveDOMHTMLDocumentMethod "hasFocus" o = WebKit2WebExtension.DOMDocument.DOMDocumentHasFocusMethodInfo
    ResolveDOMHTMLDocumentMethod "importNode" o = WebKit2WebExtension.DOMDocument.DOMDocumentImportNodeMethodInfo
    ResolveDOMHTMLDocumentMethod "insertBefore" o = WebKit2WebExtension.DOMNode.DOMNodeInsertBeforeMethodInfo
    ResolveDOMHTMLDocumentMethod "isDefaultNamespace" o = WebKit2WebExtension.DOMNode.DOMNodeIsDefaultNamespaceMethodInfo
    ResolveDOMHTMLDocumentMethod "isEqualNode" o = WebKit2WebExtension.DOMNode.DOMNodeIsEqualNodeMethodInfo
    ResolveDOMHTMLDocumentMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMHTMLDocumentMethod "isSameNode" o = WebKit2WebExtension.DOMNode.DOMNodeIsSameNodeMethodInfo
    ResolveDOMHTMLDocumentMethod "isSupported" o = WebKit2WebExtension.DOMNode.DOMNodeIsSupportedMethodInfo
    ResolveDOMHTMLDocumentMethod "lookupNamespaceUri" o = WebKit2WebExtension.DOMNode.DOMNodeLookupNamespaceUriMethodInfo
    ResolveDOMHTMLDocumentMethod "lookupPrefix" o = WebKit2WebExtension.DOMNode.DOMNodeLookupPrefixMethodInfo
    ResolveDOMHTMLDocumentMethod "normalize" o = WebKit2WebExtension.DOMNode.DOMNodeNormalizeMethodInfo
    ResolveDOMHTMLDocumentMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMHTMLDocumentMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMHTMLDocumentMethod "queryCommandEnabled" o = WebKit2WebExtension.DOMDocument.DOMDocumentQueryCommandEnabledMethodInfo
    ResolveDOMHTMLDocumentMethod "queryCommandIndeterm" o = WebKit2WebExtension.DOMDocument.DOMDocumentQueryCommandIndetermMethodInfo
    ResolveDOMHTMLDocumentMethod "queryCommandState" o = WebKit2WebExtension.DOMDocument.DOMDocumentQueryCommandStateMethodInfo
    ResolveDOMHTMLDocumentMethod "queryCommandSupported" o = WebKit2WebExtension.DOMDocument.DOMDocumentQueryCommandSupportedMethodInfo
    ResolveDOMHTMLDocumentMethod "queryCommandValue" o = WebKit2WebExtension.DOMDocument.DOMDocumentQueryCommandValueMethodInfo
    ResolveDOMHTMLDocumentMethod "querySelector" o = WebKit2WebExtension.DOMDocument.DOMDocumentQuerySelectorMethodInfo
    ResolveDOMHTMLDocumentMethod "querySelectorAll" o = WebKit2WebExtension.DOMDocument.DOMDocumentQuerySelectorAllMethodInfo
    ResolveDOMHTMLDocumentMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMHTMLDocumentMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMHTMLDocumentMethod "releaseEvents" o = DOMHTMLDocumentReleaseEventsMethodInfo
    ResolveDOMHTMLDocumentMethod "removeChild" o = WebKit2WebExtension.DOMNode.DOMNodeRemoveChildMethodInfo
    ResolveDOMHTMLDocumentMethod "removeEventListener" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetRemoveEventListenerMethodInfo
    ResolveDOMHTMLDocumentMethod "replaceChild" o = WebKit2WebExtension.DOMNode.DOMNodeReplaceChildMethodInfo
    ResolveDOMHTMLDocumentMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMHTMLDocumentMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMHTMLDocumentMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMHTMLDocumentMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMHTMLDocumentMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMHTMLDocumentMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMHTMLDocumentMethod "webkitCancelFullscreen" o = WebKit2WebExtension.DOMDocument.DOMDocumentWebkitCancelFullscreenMethodInfo
    ResolveDOMHTMLDocumentMethod "webkitExitFullscreen" o = WebKit2WebExtension.DOMDocument.DOMDocumentWebkitExitFullscreenMethodInfo
    ResolveDOMHTMLDocumentMethod "getActiveElement" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetActiveElementMethodInfo
    ResolveDOMHTMLDocumentMethod "getAlinkColor" o = DOMHTMLDocumentGetAlinkColorMethodInfo
    ResolveDOMHTMLDocumentMethod "getAnchors" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetAnchorsMethodInfo
    ResolveDOMHTMLDocumentMethod "getApplets" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetAppletsMethodInfo
    ResolveDOMHTMLDocumentMethod "getBaseUri" o = WebKit2WebExtension.DOMNode.DOMNodeGetBaseUriMethodInfo
    ResolveDOMHTMLDocumentMethod "getBgColor" o = DOMHTMLDocumentGetBgColorMethodInfo
    ResolveDOMHTMLDocumentMethod "getBody" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetBodyMethodInfo
    ResolveDOMHTMLDocumentMethod "getCharacterSet" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetCharacterSetMethodInfo
    ResolveDOMHTMLDocumentMethod "getCharset" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetCharsetMethodInfo
    ResolveDOMHTMLDocumentMethod "getChildElementCount" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetChildElementCountMethodInfo
    ResolveDOMHTMLDocumentMethod "getChildNodes" o = WebKit2WebExtension.DOMNode.DOMNodeGetChildNodesMethodInfo
    ResolveDOMHTMLDocumentMethod "getChildren" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetChildrenMethodInfo
    ResolveDOMHTMLDocumentMethod "getCompatMode" o = DOMHTMLDocumentGetCompatModeMethodInfo
    ResolveDOMHTMLDocumentMethod "getContentType" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetContentTypeMethodInfo
    ResolveDOMHTMLDocumentMethod "getCookie" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetCookieMethodInfo
    ResolveDOMHTMLDocumentMethod "getCurrentScript" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetCurrentScriptMethodInfo
    ResolveDOMHTMLDocumentMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMHTMLDocumentMethod "getDefaultCharset" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetDefaultCharsetMethodInfo
    ResolveDOMHTMLDocumentMethod "getDefaultView" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetDefaultViewMethodInfo
    ResolveDOMHTMLDocumentMethod "getDesignMode" o = DOMHTMLDocumentGetDesignModeMethodInfo
    ResolveDOMHTMLDocumentMethod "getDir" o = DOMHTMLDocumentGetDirMethodInfo
    ResolveDOMHTMLDocumentMethod "getDoctype" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetDoctypeMethodInfo
    ResolveDOMHTMLDocumentMethod "getDocumentElement" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetDocumentElementMethodInfo
    ResolveDOMHTMLDocumentMethod "getDocumentUri" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetDocumentUriMethodInfo
    ResolveDOMHTMLDocumentMethod "getDomain" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetDomainMethodInfo
    ResolveDOMHTMLDocumentMethod "getElementById" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetElementByIdMethodInfo
    ResolveDOMHTMLDocumentMethod "getElementsByClassName" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetElementsByClassNameMethodInfo
    ResolveDOMHTMLDocumentMethod "getElementsByClassNameAsHtmlCollection" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetElementsByClassNameAsHtmlCollectionMethodInfo
    ResolveDOMHTMLDocumentMethod "getElementsByName" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetElementsByNameMethodInfo
    ResolveDOMHTMLDocumentMethod "getElementsByTagName" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetElementsByTagNameMethodInfo
    ResolveDOMHTMLDocumentMethod "getElementsByTagNameAsHtmlCollection" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetElementsByTagNameAsHtmlCollectionMethodInfo
    ResolveDOMHTMLDocumentMethod "getElementsByTagNameNs" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetElementsByTagNameNsMethodInfo
    ResolveDOMHTMLDocumentMethod "getElementsByTagNameNsAsHtmlCollection" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetElementsByTagNameNsAsHtmlCollectionMethodInfo
    ResolveDOMHTMLDocumentMethod "getEmbeds" o = DOMHTMLDocumentGetEmbedsMethodInfo
    ResolveDOMHTMLDocumentMethod "getFgColor" o = DOMHTMLDocumentGetFgColorMethodInfo
    ResolveDOMHTMLDocumentMethod "getFirstChild" o = WebKit2WebExtension.DOMNode.DOMNodeGetFirstChildMethodInfo
    ResolveDOMHTMLDocumentMethod "getFirstElementChild" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetFirstElementChildMethodInfo
    ResolveDOMHTMLDocumentMethod "getForms" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetFormsMethodInfo
    ResolveDOMHTMLDocumentMethod "getHead" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetHeadMethodInfo
    ResolveDOMHTMLDocumentMethod "getHeight" o = DOMHTMLDocumentGetHeightMethodInfo
    ResolveDOMHTMLDocumentMethod "getHidden" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetHiddenMethodInfo
    ResolveDOMHTMLDocumentMethod "getImages" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetImagesMethodInfo
    ResolveDOMHTMLDocumentMethod "getImplementation" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetImplementationMethodInfo
    ResolveDOMHTMLDocumentMethod "getInputEncoding" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetInputEncodingMethodInfo
    ResolveDOMHTMLDocumentMethod "getLastChild" o = WebKit2WebExtension.DOMNode.DOMNodeGetLastChildMethodInfo
    ResolveDOMHTMLDocumentMethod "getLastElementChild" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetLastElementChildMethodInfo
    ResolveDOMHTMLDocumentMethod "getLastModified" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetLastModifiedMethodInfo
    ResolveDOMHTMLDocumentMethod "getLinkColor" o = DOMHTMLDocumentGetLinkColorMethodInfo
    ResolveDOMHTMLDocumentMethod "getLinks" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetLinksMethodInfo
    ResolveDOMHTMLDocumentMethod "getLocalName" o = WebKit2WebExtension.DOMNode.DOMNodeGetLocalNameMethodInfo
    ResolveDOMHTMLDocumentMethod "getNamespaceUri" o = WebKit2WebExtension.DOMNode.DOMNodeGetNamespaceUriMethodInfo
    ResolveDOMHTMLDocumentMethod "getNextSibling" o = WebKit2WebExtension.DOMNode.DOMNodeGetNextSiblingMethodInfo
    ResolveDOMHTMLDocumentMethod "getNodeName" o = WebKit2WebExtension.DOMNode.DOMNodeGetNodeNameMethodInfo
    ResolveDOMHTMLDocumentMethod "getNodeType" o = WebKit2WebExtension.DOMNode.DOMNodeGetNodeTypeMethodInfo
    ResolveDOMHTMLDocumentMethod "getNodeValue" o = WebKit2WebExtension.DOMNode.DOMNodeGetNodeValueMethodInfo
    ResolveDOMHTMLDocumentMethod "getOrigin" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetOriginMethodInfo
    ResolveDOMHTMLDocumentMethod "getOverrideStyle" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetOverrideStyleMethodInfo
    ResolveDOMHTMLDocumentMethod "getOwnerDocument" o = WebKit2WebExtension.DOMNode.DOMNodeGetOwnerDocumentMethodInfo
    ResolveDOMHTMLDocumentMethod "getParentElement" o = WebKit2WebExtension.DOMNode.DOMNodeGetParentElementMethodInfo
    ResolveDOMHTMLDocumentMethod "getParentNode" o = WebKit2WebExtension.DOMNode.DOMNodeGetParentNodeMethodInfo
    ResolveDOMHTMLDocumentMethod "getPlugins" o = DOMHTMLDocumentGetPluginsMethodInfo
    ResolveDOMHTMLDocumentMethod "getPointerLockElement" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetPointerLockElementMethodInfo
    ResolveDOMHTMLDocumentMethod "getPreferredStylesheetSet" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetPreferredStylesheetSetMethodInfo
    ResolveDOMHTMLDocumentMethod "getPrefix" o = WebKit2WebExtension.DOMNode.DOMNodeGetPrefixMethodInfo
    ResolveDOMHTMLDocumentMethod "getPreviousSibling" o = WebKit2WebExtension.DOMNode.DOMNodeGetPreviousSiblingMethodInfo
    ResolveDOMHTMLDocumentMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMHTMLDocumentMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMHTMLDocumentMethod "getReadyState" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetReadyStateMethodInfo
    ResolveDOMHTMLDocumentMethod "getReferrer" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetReferrerMethodInfo
    ResolveDOMHTMLDocumentMethod "getScripts" o = DOMHTMLDocumentGetScriptsMethodInfo
    ResolveDOMHTMLDocumentMethod "getScrollingElement" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetScrollingElementMethodInfo
    ResolveDOMHTMLDocumentMethod "getSelectedStylesheetSet" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetSelectedStylesheetSetMethodInfo
    ResolveDOMHTMLDocumentMethod "getStyleSheets" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetStyleSheetsMethodInfo
    ResolveDOMHTMLDocumentMethod "getTextContent" o = WebKit2WebExtension.DOMNode.DOMNodeGetTextContentMethodInfo
    ResolveDOMHTMLDocumentMethod "getTitle" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetTitleMethodInfo
    ResolveDOMHTMLDocumentMethod "getUrl" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetUrlMethodInfo
    ResolveDOMHTMLDocumentMethod "getVisibilityState" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetVisibilityStateMethodInfo
    ResolveDOMHTMLDocumentMethod "getVlinkColor" o = DOMHTMLDocumentGetVlinkColorMethodInfo
    ResolveDOMHTMLDocumentMethod "getWebkitCurrentFullscreenElement" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetWebkitCurrentFullscreenElementMethodInfo
    ResolveDOMHTMLDocumentMethod "getWebkitFullscreenElement" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetWebkitFullscreenElementMethodInfo
    ResolveDOMHTMLDocumentMethod "getWebkitFullscreenEnabled" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetWebkitFullscreenEnabledMethodInfo
    ResolveDOMHTMLDocumentMethod "getWebkitFullscreenKeyboardInputAllowed" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetWebkitFullscreenKeyboardInputAllowedMethodInfo
    ResolveDOMHTMLDocumentMethod "getWebkitIsFullscreen" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetWebkitIsFullscreenMethodInfo
    ResolveDOMHTMLDocumentMethod "getWidth" o = DOMHTMLDocumentGetWidthMethodInfo
    ResolveDOMHTMLDocumentMethod "getXmlEncoding" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetXmlEncodingMethodInfo
    ResolveDOMHTMLDocumentMethod "getXmlStandalone" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetXmlStandaloneMethodInfo
    ResolveDOMHTMLDocumentMethod "getXmlVersion" o = WebKit2WebExtension.DOMDocument.DOMDocumentGetXmlVersionMethodInfo
    ResolveDOMHTMLDocumentMethod "setAlinkColor" o = DOMHTMLDocumentSetAlinkColorMethodInfo
    ResolveDOMHTMLDocumentMethod "setBgColor" o = DOMHTMLDocumentSetBgColorMethodInfo
    ResolveDOMHTMLDocumentMethod "setBody" o = WebKit2WebExtension.DOMDocument.DOMDocumentSetBodyMethodInfo
    ResolveDOMHTMLDocumentMethod "setCharset" o = WebKit2WebExtension.DOMDocument.DOMDocumentSetCharsetMethodInfo
    ResolveDOMHTMLDocumentMethod "setCookie" o = WebKit2WebExtension.DOMDocument.DOMDocumentSetCookieMethodInfo
    ResolveDOMHTMLDocumentMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMHTMLDocumentMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMHTMLDocumentMethod "setDesignMode" o = DOMHTMLDocumentSetDesignModeMethodInfo
    ResolveDOMHTMLDocumentMethod "setDir" o = DOMHTMLDocumentSetDirMethodInfo
    ResolveDOMHTMLDocumentMethod "setDocumentUri" o = WebKit2WebExtension.DOMDocument.DOMDocumentSetDocumentUriMethodInfo
    ResolveDOMHTMLDocumentMethod "setFgColor" o = DOMHTMLDocumentSetFgColorMethodInfo
    ResolveDOMHTMLDocumentMethod "setLinkColor" o = DOMHTMLDocumentSetLinkColorMethodInfo
    ResolveDOMHTMLDocumentMethod "setNodeValue" o = WebKit2WebExtension.DOMNode.DOMNodeSetNodeValueMethodInfo
    ResolveDOMHTMLDocumentMethod "setPrefix" o = WebKit2WebExtension.DOMNode.DOMNodeSetPrefixMethodInfo
    ResolveDOMHTMLDocumentMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMHTMLDocumentMethod "setSelectedStylesheetSet" o = WebKit2WebExtension.DOMDocument.DOMDocumentSetSelectedStylesheetSetMethodInfo
    ResolveDOMHTMLDocumentMethod "setTextContent" o = WebKit2WebExtension.DOMNode.DOMNodeSetTextContentMethodInfo
    ResolveDOMHTMLDocumentMethod "setTitle" o = WebKit2WebExtension.DOMDocument.DOMDocumentSetTitleMethodInfo
    ResolveDOMHTMLDocumentMethod "setVlinkColor" o = DOMHTMLDocumentSetVlinkColorMethodInfo
    ResolveDOMHTMLDocumentMethod "setXmlStandalone" o = WebKit2WebExtension.DOMDocument.DOMDocumentSetXmlStandaloneMethodInfo
    ResolveDOMHTMLDocumentMethod "setXmlVersion" o = WebKit2WebExtension.DOMDocument.DOMDocumentSetXmlVersionMethodInfo
    ResolveDOMHTMLDocumentMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDOMHTMLDocumentMethod t DOMHTMLDocument, O.MethodInfo info DOMHTMLDocument p) => OL.IsLabel t (DOMHTMLDocument -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- VVV Prop "alink-color"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

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

-- | Set the value of the “@alink-color@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMHTMLDocument [ #alinkColor 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMHTMLDocumentAlinkColor :: (MonadIO m, IsDOMHTMLDocument o) => o -> T.Text -> m ()
setDOMHTMLDocumentAlinkColor :: o -> Text -> m ()
setDOMHTMLDocumentAlinkColor obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "alink-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@alink-color@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMHTMLDocumentAlinkColor :: (IsDOMHTMLDocument o) => T.Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentAlinkColor :: Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentAlinkColor val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "alink-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentAlinkColorPropertyInfo
instance AttrInfo DOMHTMLDocumentAlinkColorPropertyInfo where
    type AttrAllowedOps DOMHTMLDocumentAlinkColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLDocumentAlinkColorPropertyInfo = IsDOMHTMLDocument
    type AttrSetTypeConstraint DOMHTMLDocumentAlinkColorPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMHTMLDocumentAlinkColorPropertyInfo = (~) T.Text
    type AttrTransferType DOMHTMLDocumentAlinkColorPropertyInfo = T.Text
    type AttrGetType DOMHTMLDocumentAlinkColorPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMHTMLDocumentAlinkColorPropertyInfo = "alink-color"
    type AttrOrigin DOMHTMLDocumentAlinkColorPropertyInfo = DOMHTMLDocument
    attrGet = getDOMHTMLDocumentAlinkColor
    attrSet = setDOMHTMLDocumentAlinkColor
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMHTMLDocumentAlinkColor
    attrClear = undefined
#endif

-- VVV Prop "bg-color"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

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

-- | Set the value of the “@bg-color@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMHTMLDocument [ #bgColor 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMHTMLDocumentBgColor :: (MonadIO m, IsDOMHTMLDocument o) => o -> T.Text -> m ()
setDOMHTMLDocumentBgColor :: o -> Text -> m ()
setDOMHTMLDocumentBgColor obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "bg-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@bg-color@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMHTMLDocumentBgColor :: (IsDOMHTMLDocument o) => T.Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentBgColor :: Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentBgColor val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "bg-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentBgColorPropertyInfo
instance AttrInfo DOMHTMLDocumentBgColorPropertyInfo where
    type AttrAllowedOps DOMHTMLDocumentBgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLDocumentBgColorPropertyInfo = IsDOMHTMLDocument
    type AttrSetTypeConstraint DOMHTMLDocumentBgColorPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMHTMLDocumentBgColorPropertyInfo = (~) T.Text
    type AttrTransferType DOMHTMLDocumentBgColorPropertyInfo = T.Text
    type AttrGetType DOMHTMLDocumentBgColorPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMHTMLDocumentBgColorPropertyInfo = "bg-color"
    type AttrOrigin DOMHTMLDocumentBgColorPropertyInfo = DOMHTMLDocument
    attrGet = getDOMHTMLDocumentBgColor
    attrSet = setDOMHTMLDocumentBgColor
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMHTMLDocumentBgColor
    attrClear = undefined
#endif

-- VVV Prop "dir"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

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

-- | Set the value of the “@dir@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMHTMLDocument [ #dir 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMHTMLDocumentDir :: (MonadIO m, IsDOMHTMLDocument o) => o -> T.Text -> m ()
setDOMHTMLDocumentDir :: o -> Text -> m ()
setDOMHTMLDocumentDir obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "dir" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@dir@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMHTMLDocumentDir :: (IsDOMHTMLDocument o) => T.Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentDir :: Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentDir val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "dir" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentDirPropertyInfo
instance AttrInfo DOMHTMLDocumentDirPropertyInfo where
    type AttrAllowedOps DOMHTMLDocumentDirPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLDocumentDirPropertyInfo = IsDOMHTMLDocument
    type AttrSetTypeConstraint DOMHTMLDocumentDirPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMHTMLDocumentDirPropertyInfo = (~) T.Text
    type AttrTransferType DOMHTMLDocumentDirPropertyInfo = T.Text
    type AttrGetType DOMHTMLDocumentDirPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMHTMLDocumentDirPropertyInfo = "dir"
    type AttrOrigin DOMHTMLDocumentDirPropertyInfo = DOMHTMLDocument
    attrGet = getDOMHTMLDocumentDir
    attrSet = setDOMHTMLDocumentDir
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMHTMLDocumentDir
    attrClear = undefined
#endif

-- VVV Prop "fg-color"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

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

-- | Set the value of the “@fg-color@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMHTMLDocument [ #fgColor 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMHTMLDocumentFgColor :: (MonadIO m, IsDOMHTMLDocument o) => o -> T.Text -> m ()
setDOMHTMLDocumentFgColor :: o -> Text -> m ()
setDOMHTMLDocumentFgColor obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "fg-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@fg-color@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMHTMLDocumentFgColor :: (IsDOMHTMLDocument o) => T.Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentFgColor :: Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentFgColor val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "fg-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentFgColorPropertyInfo
instance AttrInfo DOMHTMLDocumentFgColorPropertyInfo where
    type AttrAllowedOps DOMHTMLDocumentFgColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLDocumentFgColorPropertyInfo = IsDOMHTMLDocument
    type AttrSetTypeConstraint DOMHTMLDocumentFgColorPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMHTMLDocumentFgColorPropertyInfo = (~) T.Text
    type AttrTransferType DOMHTMLDocumentFgColorPropertyInfo = T.Text
    type AttrGetType DOMHTMLDocumentFgColorPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMHTMLDocumentFgColorPropertyInfo = "fg-color"
    type AttrOrigin DOMHTMLDocumentFgColorPropertyInfo = DOMHTMLDocument
    attrGet = getDOMHTMLDocumentFgColor
    attrSet = setDOMHTMLDocumentFgColor
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMHTMLDocumentFgColor
    attrClear = undefined
#endif

-- VVV Prop "height"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentHeightPropertyInfo
instance AttrInfo DOMHTMLDocumentHeightPropertyInfo where
    type AttrAllowedOps DOMHTMLDocumentHeightPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLDocumentHeightPropertyInfo = IsDOMHTMLDocument
    type AttrSetTypeConstraint DOMHTMLDocumentHeightPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMHTMLDocumentHeightPropertyInfo = (~) ()
    type AttrTransferType DOMHTMLDocumentHeightPropertyInfo = ()
    type AttrGetType DOMHTMLDocumentHeightPropertyInfo = CLong
    type AttrLabel DOMHTMLDocumentHeightPropertyInfo = "height"
    type AttrOrigin DOMHTMLDocumentHeightPropertyInfo = DOMHTMLDocument
    attrGet = getDOMHTMLDocumentHeight
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "link-color"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

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

-- | Set the value of the “@link-color@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMHTMLDocument [ #linkColor 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMHTMLDocumentLinkColor :: (MonadIO m, IsDOMHTMLDocument o) => o -> T.Text -> m ()
setDOMHTMLDocumentLinkColor :: o -> Text -> m ()
setDOMHTMLDocumentLinkColor obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "link-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@link-color@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMHTMLDocumentLinkColor :: (IsDOMHTMLDocument o) => T.Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentLinkColor :: Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentLinkColor val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "link-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentLinkColorPropertyInfo
instance AttrInfo DOMHTMLDocumentLinkColorPropertyInfo where
    type AttrAllowedOps DOMHTMLDocumentLinkColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLDocumentLinkColorPropertyInfo = IsDOMHTMLDocument
    type AttrSetTypeConstraint DOMHTMLDocumentLinkColorPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMHTMLDocumentLinkColorPropertyInfo = (~) T.Text
    type AttrTransferType DOMHTMLDocumentLinkColorPropertyInfo = T.Text
    type AttrGetType DOMHTMLDocumentLinkColorPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMHTMLDocumentLinkColorPropertyInfo = "link-color"
    type AttrOrigin DOMHTMLDocumentLinkColorPropertyInfo = DOMHTMLDocument
    attrGet = getDOMHTMLDocumentLinkColor
    attrSet = setDOMHTMLDocumentLinkColor
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMHTMLDocumentLinkColor
    attrClear = undefined
#endif

-- VVV Prop "vlink-color"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Just False)

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

-- | Set the value of the “@vlink-color@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMHTMLDocument [ #vlinkColor 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMHTMLDocumentVlinkColor :: (MonadIO m, IsDOMHTMLDocument o) => o -> T.Text -> m ()
setDOMHTMLDocumentVlinkColor :: o -> Text -> m ()
setDOMHTMLDocumentVlinkColor obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "vlink-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@vlink-color@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMHTMLDocumentVlinkColor :: (IsDOMHTMLDocument o) => T.Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentVlinkColor :: Text -> IO (GValueConstruct o)
constructDOMHTMLDocumentVlinkColor val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "vlink-color" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentVlinkColorPropertyInfo
instance AttrInfo DOMHTMLDocumentVlinkColorPropertyInfo where
    type AttrAllowedOps DOMHTMLDocumentVlinkColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLDocumentVlinkColorPropertyInfo = IsDOMHTMLDocument
    type AttrSetTypeConstraint DOMHTMLDocumentVlinkColorPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMHTMLDocumentVlinkColorPropertyInfo = (~) T.Text
    type AttrTransferType DOMHTMLDocumentVlinkColorPropertyInfo = T.Text
    type AttrGetType DOMHTMLDocumentVlinkColorPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMHTMLDocumentVlinkColorPropertyInfo = "vlink-color"
    type AttrOrigin DOMHTMLDocumentVlinkColorPropertyInfo = DOMHTMLDocument
    attrGet = getDOMHTMLDocumentVlinkColor
    attrSet = setDOMHTMLDocumentVlinkColor
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMHTMLDocumentVlinkColor
    attrClear = undefined
#endif

-- VVV Prop "width"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentWidthPropertyInfo
instance AttrInfo DOMHTMLDocumentWidthPropertyInfo where
    type AttrAllowedOps DOMHTMLDocumentWidthPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMHTMLDocumentWidthPropertyInfo = IsDOMHTMLDocument
    type AttrSetTypeConstraint DOMHTMLDocumentWidthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMHTMLDocumentWidthPropertyInfo = (~) ()
    type AttrTransferType DOMHTMLDocumentWidthPropertyInfo = ()
    type AttrGetType DOMHTMLDocumentWidthPropertyInfo = CLong
    type AttrLabel DOMHTMLDocumentWidthPropertyInfo = "width"
    type AttrOrigin DOMHTMLDocumentWidthPropertyInfo = DOMHTMLDocument
    attrGet = getDOMHTMLDocumentWidth
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMHTMLDocument
type instance O.AttributeList DOMHTMLDocument = DOMHTMLDocumentAttributeList
type DOMHTMLDocumentAttributeList = ('[ '("activeElement", WebKit2WebExtension.DOMDocument.DOMDocumentActiveElementPropertyInfo), '("alinkColor", DOMHTMLDocumentAlinkColorPropertyInfo), '("anchors", WebKit2WebExtension.DOMDocument.DOMDocumentAnchorsPropertyInfo), '("applets", WebKit2WebExtension.DOMDocument.DOMDocumentAppletsPropertyInfo), '("baseUri", WebKit2WebExtension.DOMNode.DOMNodeBaseUriPropertyInfo), '("bgColor", DOMHTMLDocumentBgColorPropertyInfo), '("body", WebKit2WebExtension.DOMDocument.DOMDocumentBodyPropertyInfo), '("characterSet", WebKit2WebExtension.DOMDocument.DOMDocumentCharacterSetPropertyInfo), '("charset", WebKit2WebExtension.DOMDocument.DOMDocumentCharsetPropertyInfo), '("childElementCount", WebKit2WebExtension.DOMDocument.DOMDocumentChildElementCountPropertyInfo), '("childNodes", WebKit2WebExtension.DOMNode.DOMNodeChildNodesPropertyInfo), '("children", WebKit2WebExtension.DOMDocument.DOMDocumentChildrenPropertyInfo), '("compatMode", WebKit2WebExtension.DOMDocument.DOMDocumentCompatModePropertyInfo), '("contentType", WebKit2WebExtension.DOMDocument.DOMDocumentContentTypePropertyInfo), '("cookie", WebKit2WebExtension.DOMDocument.DOMDocumentCookiePropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("currentScript", WebKit2WebExtension.DOMDocument.DOMDocumentCurrentScriptPropertyInfo), '("defaultView", WebKit2WebExtension.DOMDocument.DOMDocumentDefaultViewPropertyInfo), '("designMode", WebKit2WebExtension.DOMDocument.DOMDocumentDesignModePropertyInfo), '("dir", DOMHTMLDocumentDirPropertyInfo), '("doctype", WebKit2WebExtension.DOMDocument.DOMDocumentDoctypePropertyInfo), '("documentElement", WebKit2WebExtension.DOMDocument.DOMDocumentDocumentElementPropertyInfo), '("documentUri", WebKit2WebExtension.DOMDocument.DOMDocumentDocumentUriPropertyInfo), '("domain", WebKit2WebExtension.DOMDocument.DOMDocumentDomainPropertyInfo), '("embeds", WebKit2WebExtension.DOMDocument.DOMDocumentEmbedsPropertyInfo), '("fgColor", DOMHTMLDocumentFgColorPropertyInfo), '("firstChild", WebKit2WebExtension.DOMNode.DOMNodeFirstChildPropertyInfo), '("firstElementChild", WebKit2WebExtension.DOMDocument.DOMDocumentFirstElementChildPropertyInfo), '("forms", WebKit2WebExtension.DOMDocument.DOMDocumentFormsPropertyInfo), '("head", WebKit2WebExtension.DOMDocument.DOMDocumentHeadPropertyInfo), '("height", DOMHTMLDocumentHeightPropertyInfo), '("hidden", WebKit2WebExtension.DOMDocument.DOMDocumentHiddenPropertyInfo), '("images", WebKit2WebExtension.DOMDocument.DOMDocumentImagesPropertyInfo), '("implementation", WebKit2WebExtension.DOMDocument.DOMDocumentImplementationPropertyInfo), '("inputEncoding", WebKit2WebExtension.DOMDocument.DOMDocumentInputEncodingPropertyInfo), '("lastChild", WebKit2WebExtension.DOMNode.DOMNodeLastChildPropertyInfo), '("lastElementChild", WebKit2WebExtension.DOMDocument.DOMDocumentLastElementChildPropertyInfo), '("lastModified", WebKit2WebExtension.DOMDocument.DOMDocumentLastModifiedPropertyInfo), '("linkColor", DOMHTMLDocumentLinkColorPropertyInfo), '("links", WebKit2WebExtension.DOMDocument.DOMDocumentLinksPropertyInfo), '("nextSibling", WebKit2WebExtension.DOMNode.DOMNodeNextSiblingPropertyInfo), '("nodeName", WebKit2WebExtension.DOMNode.DOMNodeNodeNamePropertyInfo), '("nodeType", WebKit2WebExtension.DOMNode.DOMNodeNodeTypePropertyInfo), '("nodeValue", WebKit2WebExtension.DOMNode.DOMNodeNodeValuePropertyInfo), '("origin", WebKit2WebExtension.DOMDocument.DOMDocumentOriginPropertyInfo), '("ownerDocument", WebKit2WebExtension.DOMNode.DOMNodeOwnerDocumentPropertyInfo), '("parentElement", WebKit2WebExtension.DOMNode.DOMNodeParentElementPropertyInfo), '("parentNode", WebKit2WebExtension.DOMNode.DOMNodeParentNodePropertyInfo), '("plugins", WebKit2WebExtension.DOMDocument.DOMDocumentPluginsPropertyInfo), '("pointerLockElement", WebKit2WebExtension.DOMDocument.DOMDocumentPointerLockElementPropertyInfo), '("preferredStylesheetSet", WebKit2WebExtension.DOMDocument.DOMDocumentPreferredStylesheetSetPropertyInfo), '("previousSibling", WebKit2WebExtension.DOMNode.DOMNodePreviousSiblingPropertyInfo), '("readyState", WebKit2WebExtension.DOMDocument.DOMDocumentReadyStatePropertyInfo), '("referrer", WebKit2WebExtension.DOMDocument.DOMDocumentReferrerPropertyInfo), '("scripts", WebKit2WebExtension.DOMDocument.DOMDocumentScriptsPropertyInfo), '("scrollingElement", WebKit2WebExtension.DOMDocument.DOMDocumentScrollingElementPropertyInfo), '("selectedStylesheetSet", WebKit2WebExtension.DOMDocument.DOMDocumentSelectedStylesheetSetPropertyInfo), '("styleSheets", WebKit2WebExtension.DOMDocument.DOMDocumentStyleSheetsPropertyInfo), '("textContent", WebKit2WebExtension.DOMNode.DOMNodeTextContentPropertyInfo), '("title", WebKit2WebExtension.DOMDocument.DOMDocumentTitlePropertyInfo), '("url", WebKit2WebExtension.DOMDocument.DOMDocumentUrlPropertyInfo), '("visibilityState", WebKit2WebExtension.DOMDocument.DOMDocumentVisibilityStatePropertyInfo), '("vlinkColor", DOMHTMLDocumentVlinkColorPropertyInfo), '("webkitCurrentFullScreenElement", WebKit2WebExtension.DOMDocument.DOMDocumentWebkitCurrentFullScreenElementPropertyInfo), '("webkitFullScreenKeyboardInputAllowed", WebKit2WebExtension.DOMDocument.DOMDocumentWebkitFullScreenKeyboardInputAllowedPropertyInfo), '("webkitFullscreenElement", WebKit2WebExtension.DOMDocument.DOMDocumentWebkitFullscreenElementPropertyInfo), '("webkitFullscreenEnabled", WebKit2WebExtension.DOMDocument.DOMDocumentWebkitFullscreenEnabledPropertyInfo), '("webkitIsFullScreen", WebKit2WebExtension.DOMDocument.DOMDocumentWebkitIsFullScreenPropertyInfo), '("width", DOMHTMLDocumentWidthPropertyInfo), '("xmlEncoding", WebKit2WebExtension.DOMDocument.DOMDocumentXmlEncodingPropertyInfo), '("xmlStandalone", WebKit2WebExtension.DOMDocument.DOMDocumentXmlStandalonePropertyInfo), '("xmlVersion", WebKit2WebExtension.DOMDocument.DOMDocumentXmlVersionPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMHTMLDocumentAlinkColor :: AttrLabelProxy "alinkColor"
dOMHTMLDocumentAlinkColor = AttrLabelProxy

dOMHTMLDocumentBgColor :: AttrLabelProxy "bgColor"
dOMHTMLDocumentBgColor = AttrLabelProxy

dOMHTMLDocumentDir :: AttrLabelProxy "dir"
dOMHTMLDocumentDir = AttrLabelProxy

dOMHTMLDocumentFgColor :: AttrLabelProxy "fgColor"
dOMHTMLDocumentFgColor = AttrLabelProxy

dOMHTMLDocumentHeight :: AttrLabelProxy "height"
dOMHTMLDocumentHeight = AttrLabelProxy

dOMHTMLDocumentLinkColor :: AttrLabelProxy "linkColor"
dOMHTMLDocumentLinkColor = AttrLabelProxy

dOMHTMLDocumentVlinkColor :: AttrLabelProxy "vlinkColor"
dOMHTMLDocumentVlinkColor = AttrLabelProxy

dOMHTMLDocumentWidth :: AttrLabelProxy "width"
dOMHTMLDocumentWidth = AttrLabelProxy

#endif

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

#endif

-- method DOMHTMLDocument::capture_events
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_capture_events" webkit_dom_html_document_capture_events :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO ()

{-# DEPRECATED dOMHTMLDocumentCaptureEvents ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentCaptureEvents ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m ()
dOMHTMLDocumentCaptureEvents :: a -> m ()
dOMHTMLDocumentCaptureEvents self :: a
self = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMHTMLDocument -> IO ()
webkit_dom_html_document_capture_events Ptr DOMHTMLDocument
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentCaptureEventsMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentCaptureEventsMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentCaptureEvents

#endif

-- method DOMHTMLDocument::clear
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_clear" webkit_dom_html_document_clear :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO ()

{-# DEPRECATED dOMHTMLDocumentClear ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentClear ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m ()
dOMHTMLDocumentClear :: a -> m ()
dOMHTMLDocumentClear self :: a
self = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMHTMLDocument -> IO ()
webkit_dom_html_document_clear Ptr DOMHTMLDocument
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentClearMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentClearMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentClear

#endif

-- method DOMHTMLDocument::close
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_close" webkit_dom_html_document_close :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO ()

{-# DEPRECATED dOMHTMLDocumentClose ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m ()
dOMHTMLDocumentClose :: a -> m ()
dOMHTMLDocumentClose self :: a
self = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMHTMLDocument -> IO ()
webkit_dom_html_document_close Ptr DOMHTMLDocument
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentCloseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentCloseMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentClose

#endif

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

{-# DEPRECATED dOMHTMLDocumentGetAlinkColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetAlinkColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMHTMLDocumentGetAlinkColor :: a -> m Text
dOMHTMLDocumentGetAlinkColor self :: 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 DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMHTMLDocument -> IO CString
webkit_dom_html_document_get_alink_color Ptr DOMHTMLDocument
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetAlinkColor" 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 DOMHTMLDocumentGetAlinkColorMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetAlinkColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetAlinkColor

#endif

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

{-# DEPRECATED dOMHTMLDocumentGetBgColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetBgColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMHTMLDocumentGetBgColor :: a -> m Text
dOMHTMLDocumentGetBgColor self :: 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 DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMHTMLDocument -> IO CString
webkit_dom_html_document_get_bg_color Ptr DOMHTMLDocument
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetBgColor" 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 DOMHTMLDocumentGetBgColorMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetBgColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetBgColor

#endif

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

{-# DEPRECATED dOMHTMLDocumentGetCompatMode ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMDocument.dOMDocumentGetCompatMode' instead."] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetCompatMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMHTMLDocumentGetCompatMode :: a -> m Text
dOMHTMLDocumentGetCompatMode self :: 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 DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMHTMLDocument -> IO CString
webkit_dom_html_document_get_compat_mode Ptr DOMHTMLDocument
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetCompatMode" 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 DOMHTMLDocumentGetCompatModeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetCompatModeMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetCompatMode

#endif

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

{-# DEPRECATED dOMHTMLDocumentGetDesignMode ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMDocument.dOMDocumentGetDesignMode' instead."] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetDesignMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMHTMLDocumentGetDesignMode :: a -> m Text
dOMHTMLDocumentGetDesignMode self :: 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 DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMHTMLDocument -> IO CString
webkit_dom_html_document_get_design_mode Ptr DOMHTMLDocument
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetDesignMode" 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 DOMHTMLDocumentGetDesignModeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetDesignModeMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetDesignMode

#endif

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

{-# DEPRECATED dOMHTMLDocumentGetDir ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetDir ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMHTMLDocumentGetDir :: a -> m Text
dOMHTMLDocumentGetDir self :: 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 DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMHTMLDocument -> IO CString
webkit_dom_html_document_get_dir Ptr DOMHTMLDocument
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetDir" 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 DOMHTMLDocumentGetDirMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetDirMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetDir

#endif

-- method DOMHTMLDocument::get_embeds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name
--                    { namespace = "WebKit2WebExtension" , name = "DOMHTMLCollection" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_get_embeds" webkit_dom_html_document_get_embeds :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO (Ptr WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection)

{-# DEPRECATED dOMHTMLDocumentGetEmbeds ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMDocument.dOMDocumentGetEmbeds' instead."] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetEmbeds ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMHTMLCollection.DOMHTMLCollection'
dOMHTMLDocumentGetEmbeds :: a -> m DOMHTMLCollection
dOMHTMLDocumentGetEmbeds self :: a
self = IO DOMHTMLCollection -> m DOMHTMLCollection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMHTMLCollection -> m DOMHTMLCollection)
-> IO DOMHTMLCollection -> m DOMHTMLCollection
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMHTMLCollection
result <- Ptr DOMHTMLDocument -> IO (Ptr DOMHTMLCollection)
webkit_dom_html_document_get_embeds Ptr DOMHTMLDocument
self'
    Text -> Ptr DOMHTMLCollection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetEmbeds" Ptr DOMHTMLCollection
result
    DOMHTMLCollection
result' <- ((ManagedPtr DOMHTMLCollection -> DOMHTMLCollection)
-> Ptr DOMHTMLCollection -> IO DOMHTMLCollection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DOMHTMLCollection -> DOMHTMLCollection
WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection) Ptr DOMHTMLCollection
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    DOMHTMLCollection -> IO DOMHTMLCollection
forall (m :: * -> *) a. Monad m => a -> m a
return DOMHTMLCollection
result'

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentGetEmbedsMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetEmbedsMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetEmbeds

#endif

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

{-# DEPRECATED dOMHTMLDocumentGetFgColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetFgColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMHTMLDocumentGetFgColor :: a -> m Text
dOMHTMLDocumentGetFgColor self :: 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 DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMHTMLDocument -> IO CString
webkit_dom_html_document_get_fg_color Ptr DOMHTMLDocument
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetFgColor" 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 DOMHTMLDocumentGetFgColorMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetFgColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetFgColor

#endif

-- method DOMHTMLDocument::get_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_get_height" webkit_dom_html_document_get_height :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO CLong

{-# DEPRECATED dOMHTMLDocumentGetHeight ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMHTMLDocumentGetHeight :: a -> m CLong
dOMHTMLDocumentGetHeight self :: a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMHTMLDocument -> IO CLong
webkit_dom_html_document_get_height Ptr DOMHTMLDocument
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentGetHeightMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetHeightMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetHeight

#endif

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

{-# DEPRECATED dOMHTMLDocumentGetLinkColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetLinkColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMHTMLDocumentGetLinkColor :: a -> m Text
dOMHTMLDocumentGetLinkColor self :: 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 DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMHTMLDocument -> IO CString
webkit_dom_html_document_get_link_color Ptr DOMHTMLDocument
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetLinkColor" 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 DOMHTMLDocumentGetLinkColorMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetLinkColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetLinkColor

#endif

-- method DOMHTMLDocument::get_plugins
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name
--                    { namespace = "WebKit2WebExtension" , name = "DOMHTMLCollection" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_get_plugins" webkit_dom_html_document_get_plugins :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO (Ptr WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection)

{-# DEPRECATED dOMHTMLDocumentGetPlugins ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMDocument.dOMDocumentGetPlugins' instead."] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetPlugins ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMHTMLCollection.DOMHTMLCollection'
dOMHTMLDocumentGetPlugins :: a -> m DOMHTMLCollection
dOMHTMLDocumentGetPlugins self :: a
self = IO DOMHTMLCollection -> m DOMHTMLCollection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMHTMLCollection -> m DOMHTMLCollection)
-> IO DOMHTMLCollection -> m DOMHTMLCollection
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMHTMLCollection
result <- Ptr DOMHTMLDocument -> IO (Ptr DOMHTMLCollection)
webkit_dom_html_document_get_plugins Ptr DOMHTMLDocument
self'
    Text -> Ptr DOMHTMLCollection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetPlugins" Ptr DOMHTMLCollection
result
    DOMHTMLCollection
result' <- ((ManagedPtr DOMHTMLCollection -> DOMHTMLCollection)
-> Ptr DOMHTMLCollection -> IO DOMHTMLCollection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DOMHTMLCollection -> DOMHTMLCollection
WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection) Ptr DOMHTMLCollection
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    DOMHTMLCollection -> IO DOMHTMLCollection
forall (m :: * -> *) a. Monad m => a -> m a
return DOMHTMLCollection
result'

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentGetPluginsMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetPluginsMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetPlugins

#endif

-- method DOMHTMLDocument::get_scripts
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name
--                    { namespace = "WebKit2WebExtension" , name = "DOMHTMLCollection" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_get_scripts" webkit_dom_html_document_get_scripts :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO (Ptr WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection)

{-# DEPRECATED dOMHTMLDocumentGetScripts ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMDocument.dOMDocumentGetScripts' instead."] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetScripts ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMHTMLCollection.DOMHTMLCollection'
dOMHTMLDocumentGetScripts :: a -> m DOMHTMLCollection
dOMHTMLDocumentGetScripts self :: a
self = IO DOMHTMLCollection -> m DOMHTMLCollection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMHTMLCollection -> m DOMHTMLCollection)
-> IO DOMHTMLCollection -> m DOMHTMLCollection
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMHTMLCollection
result <- Ptr DOMHTMLDocument -> IO (Ptr DOMHTMLCollection)
webkit_dom_html_document_get_scripts Ptr DOMHTMLDocument
self'
    Text -> Ptr DOMHTMLCollection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetScripts" Ptr DOMHTMLCollection
result
    DOMHTMLCollection
result' <- ((ManagedPtr DOMHTMLCollection -> DOMHTMLCollection)
-> Ptr DOMHTMLCollection -> IO DOMHTMLCollection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DOMHTMLCollection -> DOMHTMLCollection
WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection) Ptr DOMHTMLCollection
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    DOMHTMLCollection -> IO DOMHTMLCollection
forall (m :: * -> *) a. Monad m => a -> m a
return DOMHTMLCollection
result'

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentGetScriptsMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMHTMLCollection.DOMHTMLCollection), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetScriptsMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetScripts

#endif

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

{-# DEPRECATED dOMHTMLDocumentGetVlinkColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetVlinkColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMHTMLDocumentGetVlinkColor :: a -> m Text
dOMHTMLDocumentGetVlinkColor self :: 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 DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMHTMLDocument -> IO CString
webkit_dom_html_document_get_vlink_color Ptr DOMHTMLDocument
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dOMHTMLDocumentGetVlinkColor" 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 DOMHTMLDocumentGetVlinkColorMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetVlinkColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetVlinkColor

#endif

-- method DOMHTMLDocument::get_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_get_width" webkit_dom_html_document_get_width :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO CLong

{-# DEPRECATED dOMHTMLDocumentGetWidth ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMHTMLDocumentGetWidth :: a -> m CLong
dOMHTMLDocumentGetWidth self :: a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMHTMLDocument -> IO CLong
webkit_dom_html_document_get_width Ptr DOMHTMLDocument
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentGetWidthMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentGetWidthMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentGetWidth

#endif

-- method DOMHTMLDocument::release_events
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_release_events" webkit_dom_html_document_release_events :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    IO ()

{-# DEPRECATED dOMHTMLDocumentReleaseEvents ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentReleaseEvents ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> m ()
dOMHTMLDocumentReleaseEvents :: a -> m ()
dOMHTMLDocumentReleaseEvents self :: a
self = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMHTMLDocument -> IO ()
webkit_dom_html_document_release_events Ptr DOMHTMLDocument
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentReleaseEventsMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentReleaseEventsMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentReleaseEvents

#endif

-- method DOMHTMLDocument::set_alink_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_set_alink_color" webkit_dom_html_document_set_alink_color :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

{-# DEPRECATED dOMHTMLDocumentSetAlinkColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentSetAlinkColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
dOMHTMLDocumentSetAlinkColor :: a -> Text -> m ()
dOMHTMLDocumentSetAlinkColor self :: a
self value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    Ptr DOMHTMLDocument -> CString -> IO ()
webkit_dom_html_document_set_alink_color Ptr DOMHTMLDocument
self' CString
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentSetAlinkColorMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentSetAlinkColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentSetAlinkColor

#endif

-- method DOMHTMLDocument::set_bg_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_set_bg_color" webkit_dom_html_document_set_bg_color :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

{-# DEPRECATED dOMHTMLDocumentSetBgColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentSetBgColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
dOMHTMLDocumentSetBgColor :: a -> Text -> m ()
dOMHTMLDocumentSetBgColor self :: a
self value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    Ptr DOMHTMLDocument -> CString -> IO ()
webkit_dom_html_document_set_bg_color Ptr DOMHTMLDocument
self' CString
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentSetBgColorMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentSetBgColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentSetBgColor

#endif

-- method DOMHTMLDocument::set_design_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_set_design_mode" webkit_dom_html_document_set_design_mode :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

{-# DEPRECATED dOMHTMLDocumentSetDesignMode ["(Since version 2.14)","Use 'GI.WebKit2WebExtension.Objects.DOMDocument.dOMDocumentSetDesignMode' instead."] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentSetDesignMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
dOMHTMLDocumentSetDesignMode :: a -> Text -> m ()
dOMHTMLDocumentSetDesignMode self :: a
self value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    Ptr DOMHTMLDocument -> CString -> IO ()
webkit_dom_html_document_set_design_mode Ptr DOMHTMLDocument
self' CString
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentSetDesignModeMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentSetDesignModeMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentSetDesignMode

#endif

-- method DOMHTMLDocument::set_dir
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_set_dir" webkit_dom_html_document_set_dir :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

{-# DEPRECATED dOMHTMLDocumentSetDir ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentSetDir ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
dOMHTMLDocumentSetDir :: a -> Text -> m ()
dOMHTMLDocumentSetDir self :: a
self value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    Ptr DOMHTMLDocument -> CString -> IO ()
webkit_dom_html_document_set_dir Ptr DOMHTMLDocument
self' CString
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentSetDirMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentSetDirMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentSetDir

#endif

-- method DOMHTMLDocument::set_fg_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_set_fg_color" webkit_dom_html_document_set_fg_color :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

{-# DEPRECATED dOMHTMLDocumentSetFgColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentSetFgColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
dOMHTMLDocumentSetFgColor :: a -> Text -> m ()
dOMHTMLDocumentSetFgColor self :: a
self value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    Ptr DOMHTMLDocument -> CString -> IO ()
webkit_dom_html_document_set_fg_color Ptr DOMHTMLDocument
self' CString
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentSetFgColorMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentSetFgColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentSetFgColor

#endif

-- method DOMHTMLDocument::set_link_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_set_link_color" webkit_dom_html_document_set_link_color :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

{-# DEPRECATED dOMHTMLDocumentSetLinkColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentSetLinkColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
dOMHTMLDocumentSetLinkColor :: a -> Text -> m ()
dOMHTMLDocumentSetLinkColor self :: a
self value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    Ptr DOMHTMLDocument -> CString -> IO ()
webkit_dom_html_document_set_link_color Ptr DOMHTMLDocument
self' CString
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentSetLinkColorMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentSetLinkColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentSetLinkColor

#endif

-- method DOMHTMLDocument::set_vlink_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMHTMLDocument" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMHTMLDocument"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_html_document_set_vlink_color" webkit_dom_html_document_set_vlink_color :: 
    Ptr DOMHTMLDocument ->                  -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMHTMLDocument"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

{-# DEPRECATED dOMHTMLDocumentSetVlinkColor ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMHTMLDocumentSetVlinkColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMHTMLDocument a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMHTMLDocument.DOMHTMLDocument'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
dOMHTMLDocumentSetVlinkColor :: a -> Text -> m ()
dOMHTMLDocumentSetVlinkColor self :: a
self value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMHTMLDocument
self' <- a -> IO (Ptr DOMHTMLDocument)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    Ptr DOMHTMLDocument -> CString -> IO ()
webkit_dom_html_document_set_vlink_color Ptr DOMHTMLDocument
self' CString
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMHTMLDocumentSetVlinkColorMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMHTMLDocument a) => O.MethodInfo DOMHTMLDocumentSetVlinkColorMethodInfo a signature where
    overloadedMethod = dOMHTMLDocumentSetVlinkColor

#endif