{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.WebKit2WebExtension.Objects.DOMProcessingInstruction
(
DOMProcessingInstruction(..) ,
IsDOMProcessingInstruction ,
toDOMProcessingInstruction ,
#if defined(ENABLE_OVERLOADING)
ResolveDOMProcessingInstructionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DOMProcessingInstructionGetSheetMethodInfo,
#endif
dOMProcessingInstructionGetSheet ,
#if defined(ENABLE_OVERLOADING)
DOMProcessingInstructionGetTargetMethodInfo,
#endif
dOMProcessingInstructionGetTarget ,
#if defined(ENABLE_OVERLOADING)
DOMProcessingInstructionSheetPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
dOMProcessingInstructionSheet ,
#endif
getDOMProcessingInstructionSheet ,
#if defined(ENABLE_OVERLOADING)
DOMProcessingInstructionTargetPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
dOMProcessingInstructionTarget ,
#endif
getDOMProcessingInstructionTarget ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.JavaScriptCore.Objects.Value as JavaScriptCore.Value
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Interfaces.DOMEventTarget as WebKit2WebExtension.DOMEventTarget
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Interfaces.DOMNodeFilter as WebKit2WebExtension.DOMNodeFilter
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Interfaces.DOMXPathNSResolver as WebKit2WebExtension.DOMXPathNSResolver
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMAttr as WebKit2WebExtension.DOMAttr
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCDATASection as WebKit2WebExtension.DOMCDATASection
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSRule as WebKit2WebExtension.DOMCSSRule
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSRuleList as WebKit2WebExtension.DOMCSSRuleList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSStyleDeclaration as WebKit2WebExtension.DOMCSSStyleDeclaration
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCSSStyleSheet as WebKit2WebExtension.DOMCSSStyleSheet
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMCharacterData as WebKit2WebExtension.DOMCharacterData
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMClientRect as WebKit2WebExtension.DOMClientRect
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMClientRectList as WebKit2WebExtension.DOMClientRectList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMComment as WebKit2WebExtension.DOMComment
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMImplementation as WebKit2WebExtension.DOMDOMImplementation
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMSelection as WebKit2WebExtension.DOMDOMSelection
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMTokenList as WebKit2WebExtension.DOMDOMTokenList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMWindow as WebKit2WebExtension.DOMDOMWindow
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocument as WebKit2WebExtension.DOMDocument
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocumentFragment as WebKit2WebExtension.DOMDocumentFragment
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDocumentType as WebKit2WebExtension.DOMDocumentType
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMElement as WebKit2WebExtension.DOMElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMEntityReference as WebKit2WebExtension.DOMEntityReference
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMEvent as WebKit2WebExtension.DOMEvent
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLCollection as WebKit2WebExtension.DOMHTMLCollection
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLDocument as WebKit2WebExtension.DOMHTMLDocument
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLElement as WebKit2WebExtension.DOMHTMLElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLHeadElement as WebKit2WebExtension.DOMHTMLHeadElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMHTMLScriptElement as WebKit2WebExtension.DOMHTMLScriptElement
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMMediaList as WebKit2WebExtension.DOMMediaList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNamedNodeMap as WebKit2WebExtension.DOMNamedNodeMap
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNode as WebKit2WebExtension.DOMNode
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNodeIterator as WebKit2WebExtension.DOMNodeIterator
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNodeList as WebKit2WebExtension.DOMNodeList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMRange as WebKit2WebExtension.DOMRange
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMStyleSheet as WebKit2WebExtension.DOMStyleSheet
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMStyleSheetList as WebKit2WebExtension.DOMStyleSheetList
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMText as WebKit2WebExtension.DOMText
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMTreeWalker as WebKit2WebExtension.DOMTreeWalker
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMXPathExpression as WebKit2WebExtension.DOMXPathExpression
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMXPathResult as WebKit2WebExtension.DOMXPathResult
#else
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.DOMCharacterData as WebKit2WebExtension.DOMCharacterData
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNode as WebKit2WebExtension.DOMNode
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMStyleSheet as WebKit2WebExtension.DOMStyleSheet
#endif
newtype DOMProcessingInstruction = DOMProcessingInstruction (SP.ManagedPtr DOMProcessingInstruction)
deriving (DOMProcessingInstruction -> DOMProcessingInstruction -> Bool
(DOMProcessingInstruction -> DOMProcessingInstruction -> Bool)
-> (DOMProcessingInstruction -> DOMProcessingInstruction -> Bool)
-> Eq DOMProcessingInstruction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DOMProcessingInstruction -> DOMProcessingInstruction -> Bool
== :: DOMProcessingInstruction -> DOMProcessingInstruction -> Bool
$c/= :: DOMProcessingInstruction -> DOMProcessingInstruction -> Bool
/= :: DOMProcessingInstruction -> DOMProcessingInstruction -> Bool
Eq)
instance SP.ManagedPtrNewtype DOMProcessingInstruction where
toManagedPtr :: DOMProcessingInstruction -> ManagedPtr DOMProcessingInstruction
toManagedPtr (DOMProcessingInstruction ManagedPtr DOMProcessingInstruction
p) = ManagedPtr DOMProcessingInstruction
p
foreign import ccall "webkit_dom_processing_instruction_get_type"
c_webkit_dom_processing_instruction_get_type :: IO B.Types.GType
instance B.Types.TypedObject DOMProcessingInstruction where
glibType :: IO GType
glibType = IO GType
c_webkit_dom_processing_instruction_get_type
instance B.Types.GObject DOMProcessingInstruction
class (SP.GObject o, O.IsDescendantOf DOMProcessingInstruction o) => IsDOMProcessingInstruction o
instance (SP.GObject o, O.IsDescendantOf DOMProcessingInstruction o) => IsDOMProcessingInstruction o
instance O.HasParentTypes DOMProcessingInstruction
type instance O.ParentTypes DOMProcessingInstruction = '[WebKit2WebExtension.DOMCharacterData.DOMCharacterData, WebKit2WebExtension.DOMNode.DOMNode, WebKit2WebExtension.DOMObject.DOMObject, GObject.Object.Object, WebKit2WebExtension.DOMEventTarget.DOMEventTarget]
toDOMProcessingInstruction :: (MIO.MonadIO m, IsDOMProcessingInstruction o) => o -> m DOMProcessingInstruction
toDOMProcessingInstruction :: forall (m :: * -> *) o.
(MonadIO m, IsDOMProcessingInstruction o) =>
o -> m DOMProcessingInstruction
toDOMProcessingInstruction = IO DOMProcessingInstruction -> m DOMProcessingInstruction
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DOMProcessingInstruction -> m DOMProcessingInstruction)
-> (o -> IO DOMProcessingInstruction)
-> o
-> m DOMProcessingInstruction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DOMProcessingInstruction -> DOMProcessingInstruction)
-> o -> IO DOMProcessingInstruction
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DOMProcessingInstruction -> DOMProcessingInstruction
DOMProcessingInstruction
instance B.GValue.IsGValue (Maybe DOMProcessingInstruction) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_dom_processing_instruction_get_type
gvalueSet_ :: Ptr GValue -> Maybe DOMProcessingInstruction -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DOMProcessingInstruction
P.Nothing = Ptr GValue -> Ptr DOMProcessingInstruction -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DOMProcessingInstruction
forall a. Ptr a
FP.nullPtr :: FP.Ptr DOMProcessingInstruction)
gvalueSet_ Ptr GValue
gv (P.Just DOMProcessingInstruction
obj) = DOMProcessingInstruction
-> (Ptr DOMProcessingInstruction -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMProcessingInstruction
obj (Ptr GValue -> Ptr DOMProcessingInstruction -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DOMProcessingInstruction)
gvalueGet_ Ptr GValue
gv = do
Ptr DOMProcessingInstruction
ptr <- Ptr GValue -> IO (Ptr DOMProcessingInstruction)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DOMProcessingInstruction)
if Ptr DOMProcessingInstruction
ptr Ptr DOMProcessingInstruction
-> Ptr DOMProcessingInstruction -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DOMProcessingInstruction
forall a. Ptr a
FP.nullPtr
then DOMProcessingInstruction -> Maybe DOMProcessingInstruction
forall a. a -> Maybe a
P.Just (DOMProcessingInstruction -> Maybe DOMProcessingInstruction)
-> IO DOMProcessingInstruction
-> IO (Maybe DOMProcessingInstruction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DOMProcessingInstruction -> DOMProcessingInstruction)
-> Ptr DOMProcessingInstruction -> IO DOMProcessingInstruction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMProcessingInstruction -> DOMProcessingInstruction
DOMProcessingInstruction Ptr DOMProcessingInstruction
ptr
else Maybe DOMProcessingInstruction
-> IO (Maybe DOMProcessingInstruction)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DOMProcessingInstruction
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDOMProcessingInstructionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDOMProcessingInstructionMethod "addEventListener" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetAddEventListenerMethodInfo
ResolveDOMProcessingInstructionMethod "appendChild" o = WebKit2WebExtension.DOMNode.DOMNodeAppendChildMethodInfo
ResolveDOMProcessingInstructionMethod "appendData" o = WebKit2WebExtension.DOMCharacterData.DOMCharacterDataAppendDataMethodInfo
ResolveDOMProcessingInstructionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDOMProcessingInstructionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDOMProcessingInstructionMethod "cloneNodeWithError" o = WebKit2WebExtension.DOMNode.DOMNodeCloneNodeWithErrorMethodInfo
ResolveDOMProcessingInstructionMethod "compareDocumentPosition" o = WebKit2WebExtension.DOMNode.DOMNodeCompareDocumentPositionMethodInfo
ResolveDOMProcessingInstructionMethod "contains" o = WebKit2WebExtension.DOMNode.DOMNodeContainsMethodInfo
ResolveDOMProcessingInstructionMethod "deleteData" o = WebKit2WebExtension.DOMCharacterData.DOMCharacterDataDeleteDataMethodInfo
ResolveDOMProcessingInstructionMethod "dispatchEvent" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetDispatchEventMethodInfo
ResolveDOMProcessingInstructionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDOMProcessingInstructionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDOMProcessingInstructionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDOMProcessingInstructionMethod "hasChildNodes" o = WebKit2WebExtension.DOMNode.DOMNodeHasChildNodesMethodInfo
ResolveDOMProcessingInstructionMethod "insertBefore" o = WebKit2WebExtension.DOMNode.DOMNodeInsertBeforeMethodInfo
ResolveDOMProcessingInstructionMethod "insertData" o = WebKit2WebExtension.DOMCharacterData.DOMCharacterDataInsertDataMethodInfo
ResolveDOMProcessingInstructionMethod "isDefaultNamespace" o = WebKit2WebExtension.DOMNode.DOMNodeIsDefaultNamespaceMethodInfo
ResolveDOMProcessingInstructionMethod "isEqualNode" o = WebKit2WebExtension.DOMNode.DOMNodeIsEqualNodeMethodInfo
ResolveDOMProcessingInstructionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDOMProcessingInstructionMethod "isSameNode" o = WebKit2WebExtension.DOMNode.DOMNodeIsSameNodeMethodInfo
ResolveDOMProcessingInstructionMethod "isSupported" o = WebKit2WebExtension.DOMNode.DOMNodeIsSupportedMethodInfo
ResolveDOMProcessingInstructionMethod "lookupNamespaceUri" o = WebKit2WebExtension.DOMNode.DOMNodeLookupNamespaceUriMethodInfo
ResolveDOMProcessingInstructionMethod "lookupPrefix" o = WebKit2WebExtension.DOMNode.DOMNodeLookupPrefixMethodInfo
ResolveDOMProcessingInstructionMethod "normalize" o = WebKit2WebExtension.DOMNode.DOMNodeNormalizeMethodInfo
ResolveDOMProcessingInstructionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDOMProcessingInstructionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDOMProcessingInstructionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDOMProcessingInstructionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDOMProcessingInstructionMethod "removeChild" o = WebKit2WebExtension.DOMNode.DOMNodeRemoveChildMethodInfo
ResolveDOMProcessingInstructionMethod "removeEventListener" o = WebKit2WebExtension.DOMEventTarget.DOMEventTargetRemoveEventListenerMethodInfo
ResolveDOMProcessingInstructionMethod "replaceChild" o = WebKit2WebExtension.DOMNode.DOMNodeReplaceChildMethodInfo
ResolveDOMProcessingInstructionMethod "replaceData" o = WebKit2WebExtension.DOMCharacterData.DOMCharacterDataReplaceDataMethodInfo
ResolveDOMProcessingInstructionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDOMProcessingInstructionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDOMProcessingInstructionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDOMProcessingInstructionMethod "substringData" o = WebKit2WebExtension.DOMCharacterData.DOMCharacterDataSubstringDataMethodInfo
ResolveDOMProcessingInstructionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDOMProcessingInstructionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDOMProcessingInstructionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDOMProcessingInstructionMethod "getBaseUri" o = WebKit2WebExtension.DOMNode.DOMNodeGetBaseUriMethodInfo
ResolveDOMProcessingInstructionMethod "getChildNodes" o = WebKit2WebExtension.DOMNode.DOMNodeGetChildNodesMethodInfo
ResolveDOMProcessingInstructionMethod "getData" o = WebKit2WebExtension.DOMCharacterData.DOMCharacterDataGetDataMethodInfo
ResolveDOMProcessingInstructionMethod "getFirstChild" o = WebKit2WebExtension.DOMNode.DOMNodeGetFirstChildMethodInfo
ResolveDOMProcessingInstructionMethod "getLastChild" o = WebKit2WebExtension.DOMNode.DOMNodeGetLastChildMethodInfo
ResolveDOMProcessingInstructionMethod "getLength" o = WebKit2WebExtension.DOMCharacterData.DOMCharacterDataGetLengthMethodInfo
ResolveDOMProcessingInstructionMethod "getLocalName" o = WebKit2WebExtension.DOMNode.DOMNodeGetLocalNameMethodInfo
ResolveDOMProcessingInstructionMethod "getNamespaceUri" o = WebKit2WebExtension.DOMNode.DOMNodeGetNamespaceUriMethodInfo
ResolveDOMProcessingInstructionMethod "getNextSibling" o = WebKit2WebExtension.DOMNode.DOMNodeGetNextSiblingMethodInfo
ResolveDOMProcessingInstructionMethod "getNodeName" o = WebKit2WebExtension.DOMNode.DOMNodeGetNodeNameMethodInfo
ResolveDOMProcessingInstructionMethod "getNodeType" o = WebKit2WebExtension.DOMNode.DOMNodeGetNodeTypeMethodInfo
ResolveDOMProcessingInstructionMethod "getNodeValue" o = WebKit2WebExtension.DOMNode.DOMNodeGetNodeValueMethodInfo
ResolveDOMProcessingInstructionMethod "getOwnerDocument" o = WebKit2WebExtension.DOMNode.DOMNodeGetOwnerDocumentMethodInfo
ResolveDOMProcessingInstructionMethod "getParentElement" o = WebKit2WebExtension.DOMNode.DOMNodeGetParentElementMethodInfo
ResolveDOMProcessingInstructionMethod "getParentNode" o = WebKit2WebExtension.DOMNode.DOMNodeGetParentNodeMethodInfo
ResolveDOMProcessingInstructionMethod "getPrefix" o = WebKit2WebExtension.DOMNode.DOMNodeGetPrefixMethodInfo
ResolveDOMProcessingInstructionMethod "getPreviousSibling" o = WebKit2WebExtension.DOMNode.DOMNodeGetPreviousSiblingMethodInfo
ResolveDOMProcessingInstructionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDOMProcessingInstructionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDOMProcessingInstructionMethod "getSheet" o = DOMProcessingInstructionGetSheetMethodInfo
ResolveDOMProcessingInstructionMethod "getTarget" o = DOMProcessingInstructionGetTargetMethodInfo
ResolveDOMProcessingInstructionMethod "getTextContent" o = WebKit2WebExtension.DOMNode.DOMNodeGetTextContentMethodInfo
ResolveDOMProcessingInstructionMethod "setData" o = WebKit2WebExtension.DOMCharacterData.DOMCharacterDataSetDataMethodInfo
ResolveDOMProcessingInstructionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDOMProcessingInstructionMethod "setNodeValue" o = WebKit2WebExtension.DOMNode.DOMNodeSetNodeValueMethodInfo
ResolveDOMProcessingInstructionMethod "setPrefix" o = WebKit2WebExtension.DOMNode.DOMNodeSetPrefixMethodInfo
ResolveDOMProcessingInstructionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDOMProcessingInstructionMethod "setTextContent" o = WebKit2WebExtension.DOMNode.DOMNodeSetTextContentMethodInfo
ResolveDOMProcessingInstructionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDOMProcessingInstructionMethod t DOMProcessingInstruction, O.OverloadedMethod info DOMProcessingInstruction p) => OL.IsLabel t (DOMProcessingInstruction -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDOMProcessingInstructionMethod t DOMProcessingInstruction, O.OverloadedMethod info DOMProcessingInstruction p, R.HasField t DOMProcessingInstruction p) => R.HasField t DOMProcessingInstruction p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDOMProcessingInstructionMethod t DOMProcessingInstruction, O.OverloadedMethodInfo info DOMProcessingInstruction) => OL.IsLabel t (O.MethodProxy info DOMProcessingInstruction) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getDOMProcessingInstructionSheet :: (MonadIO m, IsDOMProcessingInstruction o) => o -> m (Maybe WebKit2WebExtension.DOMStyleSheet.DOMStyleSheet)
getDOMProcessingInstructionSheet :: forall (m :: * -> *) o.
(MonadIO m, IsDOMProcessingInstruction o) =>
o -> m (Maybe DOMStyleSheet)
getDOMProcessingInstructionSheet o
obj = IO (Maybe DOMStyleSheet) -> m (Maybe DOMStyleSheet)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DOMStyleSheet) -> m (Maybe DOMStyleSheet))
-> IO (Maybe DOMStyleSheet) -> m (Maybe DOMStyleSheet)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DOMStyleSheet -> DOMStyleSheet)
-> IO (Maybe DOMStyleSheet)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"sheet" ManagedPtr DOMStyleSheet -> DOMStyleSheet
WebKit2WebExtension.DOMStyleSheet.DOMStyleSheet
#if defined(ENABLE_OVERLOADING)
data DOMProcessingInstructionSheetPropertyInfo
instance AttrInfo DOMProcessingInstructionSheetPropertyInfo where
type AttrAllowedOps DOMProcessingInstructionSheetPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DOMProcessingInstructionSheetPropertyInfo = IsDOMProcessingInstruction
type AttrSetTypeConstraint DOMProcessingInstructionSheetPropertyInfo = (~) ()
type AttrTransferTypeConstraint DOMProcessingInstructionSheetPropertyInfo = (~) ()
type AttrTransferType DOMProcessingInstructionSheetPropertyInfo = ()
type AttrGetType DOMProcessingInstructionSheetPropertyInfo = (Maybe WebKit2WebExtension.DOMStyleSheet.DOMStyleSheet)
type AttrLabel DOMProcessingInstructionSheetPropertyInfo = "sheet"
type AttrOrigin DOMProcessingInstructionSheetPropertyInfo = DOMProcessingInstruction
attrGet = getDOMProcessingInstructionSheet
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMProcessingInstruction.sheet"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.31/docs/GI-WebKit2WebExtension-Objects-DOMProcessingInstruction.html#g:attr:sheet"
})
#endif
getDOMProcessingInstructionTarget :: (MonadIO m, IsDOMProcessingInstruction o) => o -> m (Maybe T.Text)
getDOMProcessingInstructionTarget :: forall (m :: * -> *) o.
(MonadIO m, IsDOMProcessingInstruction o) =>
o -> m (Maybe Text)
getDOMProcessingInstructionTarget o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"target"
#if defined(ENABLE_OVERLOADING)
data DOMProcessingInstructionTargetPropertyInfo
instance AttrInfo DOMProcessingInstructionTargetPropertyInfo where
type AttrAllowedOps DOMProcessingInstructionTargetPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DOMProcessingInstructionTargetPropertyInfo = IsDOMProcessingInstruction
type AttrSetTypeConstraint DOMProcessingInstructionTargetPropertyInfo = (~) ()
type AttrTransferTypeConstraint DOMProcessingInstructionTargetPropertyInfo = (~) ()
type AttrTransferType DOMProcessingInstructionTargetPropertyInfo = ()
type AttrGetType DOMProcessingInstructionTargetPropertyInfo = (Maybe T.Text)
type AttrLabel DOMProcessingInstructionTargetPropertyInfo = "target"
type AttrOrigin DOMProcessingInstructionTargetPropertyInfo = DOMProcessingInstruction
attrGet = getDOMProcessingInstructionTarget
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMProcessingInstruction.target"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.31/docs/GI-WebKit2WebExtension-Objects-DOMProcessingInstruction.html#g:attr:target"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMProcessingInstruction
type instance O.AttributeList DOMProcessingInstruction = DOMProcessingInstructionAttributeList
type DOMProcessingInstructionAttributeList = ('[ '("baseUri", WebKit2WebExtension.DOMNode.DOMNodeBaseUriPropertyInfo), '("childNodes", WebKit2WebExtension.DOMNode.DOMNodeChildNodesPropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("data", WebKit2WebExtension.DOMCharacterData.DOMCharacterDataDataPropertyInfo), '("firstChild", WebKit2WebExtension.DOMNode.DOMNodeFirstChildPropertyInfo), '("lastChild", WebKit2WebExtension.DOMNode.DOMNodeLastChildPropertyInfo), '("length", WebKit2WebExtension.DOMCharacterData.DOMCharacterDataLengthPropertyInfo), '("nextSibling", WebKit2WebExtension.DOMNode.DOMNodeNextSiblingPropertyInfo), '("nodeName", WebKit2WebExtension.DOMNode.DOMNodeNodeNamePropertyInfo), '("nodeType", WebKit2WebExtension.DOMNode.DOMNodeNodeTypePropertyInfo), '("nodeValue", WebKit2WebExtension.DOMNode.DOMNodeNodeValuePropertyInfo), '("ownerDocument", WebKit2WebExtension.DOMNode.DOMNodeOwnerDocumentPropertyInfo), '("parentElement", WebKit2WebExtension.DOMNode.DOMNodeParentElementPropertyInfo), '("parentNode", WebKit2WebExtension.DOMNode.DOMNodeParentNodePropertyInfo), '("previousSibling", WebKit2WebExtension.DOMNode.DOMNodePreviousSiblingPropertyInfo), '("sheet", DOMProcessingInstructionSheetPropertyInfo), '("target", DOMProcessingInstructionTargetPropertyInfo), '("textContent", WebKit2WebExtension.DOMNode.DOMNodeTextContentPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
dOMProcessingInstructionSheet :: AttrLabelProxy "sheet"
dOMProcessingInstructionSheet = AttrLabelProxy
dOMProcessingInstructionTarget :: AttrLabelProxy "target"
dOMProcessingInstructionTarget = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DOMProcessingInstruction = DOMProcessingInstructionSignalList
type DOMProcessingInstructionSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "webkit_dom_processing_instruction_get_sheet" webkit_dom_processing_instruction_get_sheet ::
Ptr DOMProcessingInstruction ->
IO (Ptr WebKit2WebExtension.DOMStyleSheet.DOMStyleSheet)
{-# DEPRECATED dOMProcessingInstructionGetSheet ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMProcessingInstructionGetSheet ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMProcessingInstruction a) =>
a
-> m WebKit2WebExtension.DOMStyleSheet.DOMStyleSheet
dOMProcessingInstructionGetSheet :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMProcessingInstruction a) =>
a -> m DOMStyleSheet
dOMProcessingInstructionGetSheet a
self = IO DOMStyleSheet -> m DOMStyleSheet
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMStyleSheet -> m DOMStyleSheet)
-> IO DOMStyleSheet -> m DOMStyleSheet
forall a b. (a -> b) -> a -> b
$ do
Ptr DOMProcessingInstruction
self' <- a -> IO (Ptr DOMProcessingInstruction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr DOMStyleSheet
result <- Ptr DOMProcessingInstruction -> IO (Ptr DOMStyleSheet)
webkit_dom_processing_instruction_get_sheet Ptr DOMProcessingInstruction
self'
Text -> Ptr DOMStyleSheet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMProcessingInstructionGetSheet" Ptr DOMStyleSheet
result
DOMStyleSheet
result' <- ((ManagedPtr DOMStyleSheet -> DOMStyleSheet)
-> Ptr DOMStyleSheet -> IO DOMStyleSheet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DOMStyleSheet -> DOMStyleSheet
WebKit2WebExtension.DOMStyleSheet.DOMStyleSheet) Ptr DOMStyleSheet
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
DOMStyleSheet -> IO DOMStyleSheet
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DOMStyleSheet
result'
#if defined(ENABLE_OVERLOADING)
data DOMProcessingInstructionGetSheetMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMStyleSheet.DOMStyleSheet), MonadIO m, IsDOMProcessingInstruction a) => O.OverloadedMethod DOMProcessingInstructionGetSheetMethodInfo a signature where
overloadedMethod = dOMProcessingInstructionGetSheet
instance O.OverloadedMethodInfo DOMProcessingInstructionGetSheetMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMProcessingInstruction.dOMProcessingInstructionGetSheet",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.31/docs/GI-WebKit2WebExtension-Objects-DOMProcessingInstruction.html#v:dOMProcessingInstructionGetSheet"
})
#endif
foreign import ccall "webkit_dom_processing_instruction_get_target" webkit_dom_processing_instruction_get_target ::
Ptr DOMProcessingInstruction ->
IO CString
{-# DEPRECATED dOMProcessingInstructionGetTarget ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
dOMProcessingInstructionGetTarget ::
(B.CallStack.HasCallStack, MonadIO m, IsDOMProcessingInstruction a) =>
a
-> m T.Text
dOMProcessingInstructionGetTarget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMProcessingInstruction a) =>
a -> m Text
dOMProcessingInstructionGetTarget a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr DOMProcessingInstruction
self' <- a -> IO (Ptr DOMProcessingInstruction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr DOMProcessingInstruction -> IO CString
webkit_dom_processing_instruction_get_target Ptr DOMProcessingInstruction
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMProcessingInstructionGetTarget" 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DOMProcessingInstructionGetTargetMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMProcessingInstruction a) => O.OverloadedMethod DOMProcessingInstructionGetTargetMethodInfo a signature where
overloadedMethod = dOMProcessingInstructionGetTarget
instance O.OverloadedMethodInfo DOMProcessingInstructionGetTargetMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMProcessingInstruction.dOMProcessingInstructionGetTarget",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.31/docs/GI-WebKit2WebExtension-Objects-DOMProcessingInstruction.html#v:dOMProcessingInstructionGetTarget"
})
#endif