{-# LANGUAGE PatternSynonyms #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} module JSDOM.Generated.Document (getAnimations, getAnimations_, newDocument, getElementsByTagName, getElementsByTagName_, getElementsByTagNameNS, getElementsByTagNameNS_, getElementsByClassName, getElementsByClassName_, createElement, createElement_, createElementNS, createElementNS_, createDocumentFragment, createDocumentFragment_, createTextNode, createTextNode_, createCDATASection, createCDATASection_, createComment, createComment_, createProcessingInstruction, createProcessingInstruction_, importNode, importNode_, adoptNode, adoptNode_, createAttribute, createAttribute_, createAttributeNS, createAttributeNS_, createEvent, createEvent_, createRange, createRange_, createNodeIterator, createNodeIterator_, createTreeWalker, createTreeWalker_, getElementsByName, getElementsByName_, hasFocus, hasFocus_, execCommand, execCommand_, queryCommandEnabled, queryCommandEnabled_, queryCommandIndeterm, queryCommandIndeterm_, queryCommandState, queryCommandState_, queryCommandSupported, queryCommandSupported_, queryCommandValue, queryCommandValue_, getSelection, getSelection_, getSelectionUnsafe, getSelectionUnchecked, createExpression, createExpression_, createNSResolver, createNSResolver_, evaluate, evaluate_, webkitExitFullscreen, webkitCancelFullScreen, exitPointerLock, getOverrideStyle, getOverrideStyle_, caretRangeFromPoint, caretRangeFromPoint_, getCSSCanvasContext, getCSSCanvasContext_, webkitGetNamedFlows, webkitGetNamedFlows_, createTouch, createTouch_, createTouchList, createTouchList_, getTimeline, getImplementation, getURL, getDocumentURI, getOrigin, getCompatMode, getCharacterSet, getCharset, getInputEncoding, getContentType, getDoctype, getDoctypeUnsafe, getDoctypeUnchecked, getDocumentElement, getDocumentElementUnsafe, getDocumentElementUnchecked, getLocation, getLocationUnsafe, getLocationUnchecked, setDomain, getDomain, getReferrer, setCookie, getCookie, getLastModified, getReadyState, setTitle, getTitle, setDir, getDir, setBody, getBody, getBodyUnsafe, getBodyUnchecked, getHead, getHeadUnsafe, getHeadUnchecked, getImages, getEmbeds, getPlugins, getLinks, getForms, getScripts, getCurrentScript, getCurrentScriptUnsafe, getCurrentScriptUnchecked, getDefaultView, getDefaultViewUnsafe, getDefaultViewUnchecked, setDesignMode, getDesignMode, readyStateChange, getStyleSheets, getScrollingElement, getScrollingElementUnsafe, getScrollingElementUnchecked, getWebkitFullscreenEnabled, getWebkitFullscreenElement, getWebkitFullscreenElementUnsafe, getWebkitFullscreenElementUnchecked, getWebkitIsFullScreen, getWebkitFullScreenKeyboardInputAllowed, getWebkitCurrentFullScreenElement, webKitFullscreenChange, webKitFullscreenError, pointerlockchange, pointerlockerror, getFonts, getHidden, getVisibilityState, visibilitychange, getApplets, getAnchors, getPreferredStylesheetSet, getPreferredStylesheetSetUnsafe, getPreferredStylesheetSetUnchecked, setSelectedStylesheetSet, getSelectedStylesheetSet, getSelectedStylesheetSetUnsafe, getSelectedStylesheetSetUnchecked, getXmlEncoding, getXmlEncodingUnsafe, getXmlEncodingUnchecked, setXmlVersion, getXmlVersion, getXmlVersionUnsafe, getXmlVersionUnchecked, setXmlStandalone, getXmlStandalone, selectStart, selectionchange, getRootElement, getRootElementUnsafe, getRootElementUnchecked, Document(..), gTypeDocument, IsDocument, toDocument) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, realToFrac, fmap, Show, Read, Eq, Ord, Maybe(..)) import qualified Prelude (error) import Data.Typeable (Typeable) import Data.Traversable (mapM) import Language.Javascript.JSaddle (JSM(..), JSVal(..), JSString, strictEqual, toJSVal, valToStr, valToNumber, valToBool, js, jss, jsf, jsg, function, asyncFunction, new, array, jsUndefined, (!), (!!)) import Data.Int (Int64) import Data.Word (Word, Word64) import JSDOM.Types import Control.Applicative ((<$>)) import Control.Monad (void) import Control.Lens.Operators ((^.)) import JSDOM.EventTargetClosures (EventName, unsafeEventName, unsafeEventNameAsync) import JSDOM.Enums -- | getAnimations :: (MonadDOM m, IsDocument self) => self -> m [Animation] getAnimations self = liftDOM (((toDocument self) ^. jsf "getAnimations" ()) >>= fromJSArrayUnchecked) -- | getAnimations_ :: (MonadDOM m, IsDocument self) => self -> m () getAnimations_ self = liftDOM (void ((toDocument self) ^. jsf "getAnimations" ())) -- | newDocument :: (MonadDOM m) => m Document newDocument = liftDOM (Document <$> new (jsg "Document") ()) -- | getElementsByTagName :: (MonadDOM m, IsDocument self, ToJSString qualifiedName) => self -> qualifiedName -> m HTMLCollection getElementsByTagName self qualifiedName = liftDOM (((toDocument self) ^. jsf "getElementsByTagName" [toJSVal qualifiedName]) >>= fromJSValUnchecked) -- | getElementsByTagName_ :: (MonadDOM m, IsDocument self, ToJSString qualifiedName) => self -> qualifiedName -> m () getElementsByTagName_ self qualifiedName = liftDOM (void ((toDocument self) ^. jsf "getElementsByTagName" [toJSVal qualifiedName])) -- | getElementsByTagNameNS :: (MonadDOM m, IsDocument self, ToJSString namespaceURI, ToJSString localName) => self -> Maybe namespaceURI -> localName -> m HTMLCollection getElementsByTagNameNS self namespaceURI localName = liftDOM (((toDocument self) ^. jsf "getElementsByTagNameNS" [toJSVal namespaceURI, toJSVal localName]) >>= fromJSValUnchecked) -- | getElementsByTagNameNS_ :: (MonadDOM m, IsDocument self, ToJSString namespaceURI, ToJSString localName) => self -> Maybe namespaceURI -> localName -> m () getElementsByTagNameNS_ self namespaceURI localName = liftDOM (void ((toDocument self) ^. jsf "getElementsByTagNameNS" [toJSVal namespaceURI, toJSVal localName])) -- | getElementsByClassName :: (MonadDOM m, IsDocument self, ToJSString classNames) => self -> classNames -> m HTMLCollection getElementsByClassName self classNames = liftDOM (((toDocument self) ^. jsf "getElementsByClassName" [toJSVal classNames]) >>= fromJSValUnchecked) -- | getElementsByClassName_ :: (MonadDOM m, IsDocument self, ToJSString classNames) => self -> classNames -> m () getElementsByClassName_ self classNames = liftDOM (void ((toDocument self) ^. jsf "getElementsByClassName" [toJSVal classNames])) -- | createElement :: (MonadDOM m, IsDocument self, ToJSString localName) => self -> localName -> m Element createElement self localName = liftDOM (((toDocument self) ^. jsf "createElement" [toJSVal localName]) >>= fromJSValUnchecked) -- | createElement_ :: (MonadDOM m, IsDocument self, ToJSString localName) => self -> localName -> m () createElement_ self localName = liftDOM (void ((toDocument self) ^. jsf "createElement" [toJSVal localName])) -- | createElementNS :: (MonadDOM m, IsDocument self, ToJSString namespaceURI, ToJSString qualifiedName) => self -> Maybe namespaceURI -> qualifiedName -> m Element createElementNS self namespaceURI qualifiedName = liftDOM (((toDocument self) ^. jsf "createElementNS" [toJSVal namespaceURI, toJSVal qualifiedName]) >>= fromJSValUnchecked) -- | createElementNS_ :: (MonadDOM m, IsDocument self, ToJSString namespaceURI, ToJSString qualifiedName) => self -> Maybe namespaceURI -> qualifiedName -> m () createElementNS_ self namespaceURI qualifiedName = liftDOM (void ((toDocument self) ^. jsf "createElementNS" [toJSVal namespaceURI, toJSVal qualifiedName])) -- | createDocumentFragment :: (MonadDOM m, IsDocument self) => self -> m DocumentFragment createDocumentFragment self = liftDOM (((toDocument self) ^. jsf "createDocumentFragment" ()) >>= fromJSValUnchecked) -- | createDocumentFragment_ :: (MonadDOM m, IsDocument self) => self -> m () createDocumentFragment_ self = liftDOM (void ((toDocument self) ^. jsf "createDocumentFragment" ())) -- | createTextNode :: (MonadDOM m, IsDocument self, ToJSString data') => self -> data' -> m Text createTextNode self data' = liftDOM (((toDocument self) ^. jsf "createTextNode" [toJSVal data']) >>= fromJSValUnchecked) -- | createTextNode_ :: (MonadDOM m, IsDocument self, ToJSString data') => self -> data' -> m () createTextNode_ self data' = liftDOM (void ((toDocument self) ^. jsf "createTextNode" [toJSVal data'])) -- | createCDATASection :: (MonadDOM m, IsDocument self, ToJSString data') => self -> data' -> m CDATASection createCDATASection self data' = liftDOM (((toDocument self) ^. jsf "createCDATASection" [toJSVal data']) >>= fromJSValUnchecked) -- | createCDATASection_ :: (MonadDOM m, IsDocument self, ToJSString data') => self -> data' -> m () createCDATASection_ self data' = liftDOM (void ((toDocument self) ^. jsf "createCDATASection" [toJSVal data'])) -- | createComment :: (MonadDOM m, IsDocument self, ToJSString data') => self -> data' -> m Comment createComment self data' = liftDOM (((toDocument self) ^. jsf "createComment" [toJSVal data']) >>= fromJSValUnchecked) -- | createComment_ :: (MonadDOM m, IsDocument self, ToJSString data') => self -> data' -> m () createComment_ self data' = liftDOM (void ((toDocument self) ^. jsf "createComment" [toJSVal data'])) -- | createProcessingInstruction :: (MonadDOM m, IsDocument self, ToJSString target, ToJSString data') => self -> target -> data' -> m ProcessingInstruction createProcessingInstruction self target data' = liftDOM (((toDocument self) ^. jsf "createProcessingInstruction" [toJSVal target, toJSVal data']) >>= fromJSValUnchecked) -- | createProcessingInstruction_ :: (MonadDOM m, IsDocument self, ToJSString target, ToJSString data') => self -> target -> data' -> m () createProcessingInstruction_ self target data' = liftDOM (void ((toDocument self) ^. jsf "createProcessingInstruction" [toJSVal target, toJSVal data'])) -- | importNode :: (MonadDOM m, IsDocument self, IsNode node) => self -> node -> Bool -> m Node importNode self node deep = liftDOM (((toDocument self) ^. jsf "importNode" [toJSVal node, toJSVal deep]) >>= fromJSValUnchecked) -- | importNode_ :: (MonadDOM m, IsDocument self, IsNode node) => self -> node -> Bool -> m () importNode_ self node deep = liftDOM (void ((toDocument self) ^. jsf "importNode" [toJSVal node, toJSVal deep])) -- | adoptNode :: (MonadDOM m, IsDocument self, IsNode node) => self -> node -> m Node adoptNode self node = liftDOM (((toDocument self) ^. jsf "adoptNode" [toJSVal node]) >>= fromJSValUnchecked) -- | adoptNode_ :: (MonadDOM m, IsDocument self, IsNode node) => self -> node -> m () adoptNode_ self node = liftDOM (void ((toDocument self) ^. jsf "adoptNode" [toJSVal node])) -- | createAttribute :: (MonadDOM m, IsDocument self, ToJSString localName) => self -> localName -> m Attr createAttribute self localName = liftDOM (((toDocument self) ^. jsf "createAttribute" [toJSVal localName]) >>= fromJSValUnchecked) -- | createAttribute_ :: (MonadDOM m, IsDocument self, ToJSString localName) => self -> localName -> m () createAttribute_ self localName = liftDOM (void ((toDocument self) ^. jsf "createAttribute" [toJSVal localName])) -- | createAttributeNS :: (MonadDOM m, IsDocument self, ToJSString namespaceURI, ToJSString qualifiedName) => self -> Maybe namespaceURI -> qualifiedName -> m Attr createAttributeNS self namespaceURI qualifiedName = liftDOM (((toDocument self) ^. jsf "createAttributeNS" [toJSVal namespaceURI, toJSVal qualifiedName]) >>= fromJSValUnchecked) -- | createAttributeNS_ :: (MonadDOM m, IsDocument self, ToJSString namespaceURI, ToJSString qualifiedName) => self -> Maybe namespaceURI -> qualifiedName -> m () createAttributeNS_ self namespaceURI qualifiedName = liftDOM (void ((toDocument self) ^. jsf "createAttributeNS" [toJSVal namespaceURI, toJSVal qualifiedName])) -- | createEvent :: (MonadDOM m, IsDocument self, ToJSString type') => self -> type' -> m Event createEvent self type' = liftDOM (((toDocument self) ^. jsf "createEvent" [toJSVal type']) >>= fromJSValUnchecked) -- | createEvent_ :: (MonadDOM m, IsDocument self, ToJSString type') => self -> type' -> m () createEvent_ self type' = liftDOM (void ((toDocument self) ^. jsf "createEvent" [toJSVal type'])) -- | createRange :: (MonadDOM m, IsDocument self) => self -> m Range createRange self = liftDOM (((toDocument self) ^. jsf "createRange" ()) >>= fromJSValUnchecked) -- | createRange_ :: (MonadDOM m, IsDocument self) => self -> m () createRange_ self = liftDOM (void ((toDocument self) ^. jsf "createRange" ())) -- | createNodeIterator :: (MonadDOM m, IsDocument self, IsNode root) => self -> root -> Maybe Word -> Maybe NodeFilter -> m NodeIterator createNodeIterator self root whatToShow filter = liftDOM (((toDocument self) ^. jsf "createNodeIterator" [toJSVal root, toJSVal whatToShow, toJSVal filter]) >>= fromJSValUnchecked) -- | createNodeIterator_ :: (MonadDOM m, IsDocument self, IsNode root) => self -> root -> Maybe Word -> Maybe NodeFilter -> m () createNodeIterator_ self root whatToShow filter = liftDOM (void ((toDocument self) ^. jsf "createNodeIterator" [toJSVal root, toJSVal whatToShow, toJSVal filter])) -- | createTreeWalker :: (MonadDOM m, IsDocument self, IsNode root) => self -> root -> Maybe Word -> Maybe NodeFilter -> m TreeWalker createTreeWalker self root whatToShow filter = liftDOM (((toDocument self) ^. jsf "createTreeWalker" [toJSVal root, toJSVal whatToShow, toJSVal filter]) >>= fromJSValUnchecked) -- | createTreeWalker_ :: (MonadDOM m, IsDocument self, IsNode root) => self -> root -> Maybe Word -> Maybe NodeFilter -> m () createTreeWalker_ self root whatToShow filter = liftDOM (void ((toDocument self) ^. jsf "createTreeWalker" [toJSVal root, toJSVal whatToShow, toJSVal filter])) -- | getElementsByName :: (MonadDOM m, IsDocument self, ToJSString elementName) => self -> elementName -> m NodeList getElementsByName self elementName = liftDOM (((toDocument self) ^. jsf "getElementsByName" [toJSVal elementName]) >>= fromJSValUnchecked) -- | getElementsByName_ :: (MonadDOM m, IsDocument self, ToJSString elementName) => self -> elementName -> m () getElementsByName_ self elementName = liftDOM (void ((toDocument self) ^. jsf "getElementsByName" [toJSVal elementName])) -- | hasFocus :: (MonadDOM m, IsDocument self) => self -> m Bool hasFocus self = liftDOM (((toDocument self) ^. jsf "hasFocus" ()) >>= valToBool) -- | hasFocus_ :: (MonadDOM m, IsDocument self) => self -> m () hasFocus_ self = liftDOM (void ((toDocument self) ^. jsf "hasFocus" ())) -- | execCommand :: (MonadDOM m, IsDocument self, ToJSString commandId, ToJSString value) => self -> commandId -> Bool -> Maybe value -> m Bool execCommand self commandId showUI value = liftDOM (((toDocument self) ^. jsf "execCommand" [toJSVal commandId, toJSVal showUI, toJSVal value]) >>= valToBool) -- | execCommand_ :: (MonadDOM m, IsDocument self, ToJSString commandId, ToJSString value) => self -> commandId -> Bool -> Maybe value -> m () execCommand_ self commandId showUI value = liftDOM (void ((toDocument self) ^. jsf "execCommand" [toJSVal commandId, toJSVal showUI, toJSVal value])) -- | queryCommandEnabled :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m Bool queryCommandEnabled self commandId = liftDOM (((toDocument self) ^. jsf "queryCommandEnabled" [toJSVal commandId]) >>= valToBool) -- | queryCommandEnabled_ :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m () queryCommandEnabled_ self commandId = liftDOM (void ((toDocument self) ^. jsf "queryCommandEnabled" [toJSVal commandId])) -- | queryCommandIndeterm :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m Bool queryCommandIndeterm self commandId = liftDOM (((toDocument self) ^. jsf "queryCommandIndeterm" [toJSVal commandId]) >>= valToBool) -- | queryCommandIndeterm_ :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m () queryCommandIndeterm_ self commandId = liftDOM (void ((toDocument self) ^. jsf "queryCommandIndeterm" [toJSVal commandId])) -- | queryCommandState :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m Bool queryCommandState self commandId = liftDOM (((toDocument self) ^. jsf "queryCommandState" [toJSVal commandId]) >>= valToBool) -- | queryCommandState_ :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m () queryCommandState_ self commandId = liftDOM (void ((toDocument self) ^. jsf "queryCommandState" [toJSVal commandId])) -- | queryCommandSupported :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m Bool queryCommandSupported self commandId = liftDOM (((toDocument self) ^. jsf "queryCommandSupported" [toJSVal commandId]) >>= valToBool) -- | queryCommandSupported_ :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m () queryCommandSupported_ self commandId = liftDOM (void ((toDocument self) ^. jsf "queryCommandSupported" [toJSVal commandId])) -- | queryCommandValue :: (MonadDOM m, IsDocument self, ToJSString commandId, FromJSString result) => self -> commandId -> m result queryCommandValue self commandId = liftDOM (((toDocument self) ^. jsf "queryCommandValue" [toJSVal commandId]) >>= fromJSValUnchecked) -- | queryCommandValue_ :: (MonadDOM m, IsDocument self, ToJSString commandId) => self -> commandId -> m () queryCommandValue_ self commandId = liftDOM (void ((toDocument self) ^. jsf "queryCommandValue" [toJSVal commandId])) -- | getSelection :: (MonadDOM m, IsDocument self) => self -> m (Maybe Selection) getSelection self = liftDOM (((toDocument self) ^. jsf "getSelection" ()) >>= fromJSVal) -- | getSelection_ :: (MonadDOM m, IsDocument self) => self -> m () getSelection_ self = liftDOM (void ((toDocument self) ^. jsf "getSelection" ())) -- | getSelectionUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m Selection getSelectionUnsafe self = liftDOM ((((toDocument self) ^. jsf "getSelection" ()) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getSelectionUnchecked :: (MonadDOM m, IsDocument self) => self -> m Selection getSelectionUnchecked self = liftDOM (((toDocument self) ^. jsf "getSelection" ()) >>= fromJSValUnchecked) -- | createExpression :: (MonadDOM m, IsDocument self, ToJSString expression) => self -> Maybe expression -> Maybe XPathNSResolver -> m XPathExpression createExpression self expression resolver = liftDOM (((toDocument self) ^. jsf "createExpression" [toJSVal expression, toJSVal resolver]) >>= fromJSValUnchecked) -- | createExpression_ :: (MonadDOM m, IsDocument self, ToJSString expression) => self -> Maybe expression -> Maybe XPathNSResolver -> m () createExpression_ self expression resolver = liftDOM (void ((toDocument self) ^. jsf "createExpression" [toJSVal expression, toJSVal resolver])) -- | createNSResolver :: (MonadDOM m, IsDocument self, IsNode nodeResolver) => self -> Maybe nodeResolver -> m XPathNSResolver createNSResolver self nodeResolver = liftDOM (((toDocument self) ^. jsf "createNSResolver" [toJSVal nodeResolver]) >>= fromJSValUnchecked) -- | createNSResolver_ :: (MonadDOM m, IsDocument self, IsNode nodeResolver) => self -> Maybe nodeResolver -> m () createNSResolver_ self nodeResolver = liftDOM (void ((toDocument self) ^. jsf "createNSResolver" [toJSVal nodeResolver])) -- | evaluate :: (MonadDOM m, IsDocument self, ToJSString expression, IsNode contextNode) => self -> Maybe expression -> Maybe contextNode -> Maybe XPathNSResolver -> Maybe Word -> Maybe XPathResult -> m XPathResult evaluate self expression contextNode resolver type' inResult = liftDOM (((toDocument self) ^. jsf "evaluate" [toJSVal expression, toJSVal contextNode, toJSVal resolver, toJSVal type', toJSVal inResult]) >>= fromJSValUnchecked) -- | evaluate_ :: (MonadDOM m, IsDocument self, ToJSString expression, IsNode contextNode) => self -> Maybe expression -> Maybe contextNode -> Maybe XPathNSResolver -> Maybe Word -> Maybe XPathResult -> m () evaluate_ self expression contextNode resolver type' inResult = liftDOM (void ((toDocument self) ^. jsf "evaluate" [toJSVal expression, toJSVal contextNode, toJSVal resolver, toJSVal type', toJSVal inResult])) -- | webkitExitFullscreen :: (MonadDOM m, IsDocument self) => self -> m () webkitExitFullscreen self = liftDOM (void ((toDocument self) ^. jsf "webkitExitFullscreen" ())) -- | webkitCancelFullScreen :: (MonadDOM m, IsDocument self) => self -> m () webkitCancelFullScreen self = liftDOM (void ((toDocument self) ^. jsf "webkitCancelFullScreen" ())) -- | exitPointerLock :: (MonadDOM m, IsDocument self) => self -> m () exitPointerLock self = liftDOM (void ((toDocument self) ^. jsf "exitPointerLock" ())) -- | getOverrideStyle :: (MonadDOM m, IsDocument self, IsElement element, ToJSString pseudoElement) => self -> Maybe element -> Maybe pseudoElement -> m CSSStyleDeclaration getOverrideStyle self element pseudoElement = liftDOM (((toDocument self) ^. jsf "getOverrideStyle" [toJSVal element, toJSVal pseudoElement]) >>= fromJSValUnchecked) -- | getOverrideStyle_ :: (MonadDOM m, IsDocument self, IsElement element, ToJSString pseudoElement) => self -> Maybe element -> Maybe pseudoElement -> m () getOverrideStyle_ self element pseudoElement = liftDOM (void ((toDocument self) ^. jsf "getOverrideStyle" [toJSVal element, toJSVal pseudoElement])) -- | caretRangeFromPoint :: (MonadDOM m, IsDocument self) => self -> Maybe Int -> Maybe Int -> m Range caretRangeFromPoint self x y = liftDOM (((toDocument self) ^. jsf "caretRangeFromPoint" [toJSVal x, toJSVal y]) >>= fromJSValUnchecked) -- | caretRangeFromPoint_ :: (MonadDOM m, IsDocument self) => self -> Maybe Int -> Maybe Int -> m () caretRangeFromPoint_ self x y = liftDOM (void ((toDocument self) ^. jsf "caretRangeFromPoint" [toJSVal x, toJSVal y])) -- | getCSSCanvasContext :: (MonadDOM m, IsDocument self, ToJSString contextId, ToJSString name) => self -> contextId -> name -> Int -> Int -> m RenderingContext getCSSCanvasContext self contextId name width height = liftDOM (((toDocument self) ^. jsf "getCSSCanvasContext" [toJSVal contextId, toJSVal name, toJSVal width, toJSVal height]) >>= fromJSValUnchecked) -- | getCSSCanvasContext_ :: (MonadDOM m, IsDocument self, ToJSString contextId, ToJSString name) => self -> contextId -> name -> Int -> Int -> m () getCSSCanvasContext_ self contextId name width height = liftDOM (void ((toDocument self) ^. jsf "getCSSCanvasContext" [toJSVal contextId, toJSVal name, toJSVal width, toJSVal height])) -- | webkitGetNamedFlows :: (MonadDOM m, IsDocument self) => self -> m DOMNamedFlowCollection webkitGetNamedFlows self = liftDOM (((toDocument self) ^. jsf "webkitGetNamedFlows" ()) >>= fromJSValUnchecked) -- | webkitGetNamedFlows_ :: (MonadDOM m, IsDocument self) => self -> m () webkitGetNamedFlows_ self = liftDOM (void ((toDocument self) ^. jsf "webkitGetNamedFlows" ())) -- | createTouch :: (MonadDOM m, IsDocument self, IsEventTarget target) => self -> Maybe Window -> Maybe target -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Float -> Maybe Float -> m Touch createTouch self window target identifier pageX pageY screenX screenY webkitRadiusX webkitRadiusY webkitRotationAngle webkitForce = liftDOM (((toDocument self) ^. jsf "createTouch" [toJSVal window, toJSVal target, toJSVal identifier, toJSVal pageX, toJSVal pageY, toJSVal screenX, toJSVal screenY, toJSVal webkitRadiusX, toJSVal webkitRadiusY, toJSVal webkitRotationAngle, toJSVal webkitForce]) >>= fromJSValUnchecked) -- | createTouch_ :: (MonadDOM m, IsDocument self, IsEventTarget target) => self -> Maybe Window -> Maybe target -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Float -> Maybe Float -> m () createTouch_ self window target identifier pageX pageY screenX screenY webkitRadiusX webkitRadiusY webkitRotationAngle webkitForce = liftDOM (void ((toDocument self) ^. jsf "createTouch" [toJSVal window, toJSVal target, toJSVal identifier, toJSVal pageX, toJSVal pageY, toJSVal screenX, toJSVal screenY, toJSVal webkitRadiusX, toJSVal webkitRadiusY, toJSVal webkitRotationAngle, toJSVal webkitForce])) -- | createTouchList :: (MonadDOM m, IsDocument self) => self -> [Touch] -> m TouchList createTouchList self touches = liftDOM (((toDocument self) ^. jsf "createTouchList" [toJSVal (array touches)]) >>= fromJSValUnchecked) -- | createTouchList_ :: (MonadDOM m, IsDocument self) => self -> [Touch] -> m () createTouchList_ self touches = liftDOM (void ((toDocument self) ^. jsf "createTouchList" [toJSVal (array touches)])) -- | getTimeline :: (MonadDOM m, IsDocument self) => self -> m DocumentTimeline getTimeline self = liftDOM (((toDocument self) ^. js "timeline") >>= fromJSValUnchecked) -- | getImplementation :: (MonadDOM m, IsDocument self) => self -> m DOMImplementation getImplementation self = liftDOM (((toDocument self) ^. js "implementation") >>= fromJSValUnchecked) -- | getURL :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getURL self = liftDOM (((toDocument self) ^. js "URL") >>= fromJSValUnchecked) -- | getDocumentURI :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getDocumentURI self = liftDOM (((toDocument self) ^. js "documentURI") >>= fromJSValUnchecked) -- | getOrigin :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getOrigin self = liftDOM (((toDocument self) ^. js "origin") >>= fromJSValUnchecked) -- | getCompatMode :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getCompatMode self = liftDOM (((toDocument self) ^. js "compatMode") >>= fromJSValUnchecked) -- | getCharacterSet :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getCharacterSet self = liftDOM (((toDocument self) ^. js "characterSet") >>= fromJSValUnchecked) -- | getCharset :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getCharset self = liftDOM (((toDocument self) ^. js "charset") >>= fromJSValUnchecked) -- | getInputEncoding :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getInputEncoding self = liftDOM (((toDocument self) ^. js "inputEncoding") >>= fromJSValUnchecked) -- | getContentType :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getContentType self = liftDOM (((toDocument self) ^. js "contentType") >>= fromJSValUnchecked) -- | getDoctype :: (MonadDOM m, IsDocument self) => self -> m (Maybe DocumentType) getDoctype self = liftDOM (((toDocument self) ^. js "doctype") >>= fromJSVal) -- | getDoctypeUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m DocumentType getDoctypeUnsafe self = liftDOM ((((toDocument self) ^. js "doctype") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getDoctypeUnchecked :: (MonadDOM m, IsDocument self) => self -> m DocumentType getDoctypeUnchecked self = liftDOM (((toDocument self) ^. js "doctype") >>= fromJSValUnchecked) -- | getDocumentElement :: (MonadDOM m, IsDocument self) => self -> m (Maybe Element) getDocumentElement self = liftDOM (((toDocument self) ^. js "documentElement") >>= fromJSVal) -- | getDocumentElementUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m Element getDocumentElementUnsafe self = liftDOM ((((toDocument self) ^. js "documentElement") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getDocumentElementUnchecked :: (MonadDOM m, IsDocument self) => self -> m Element getDocumentElementUnchecked self = liftDOM (((toDocument self) ^. js "documentElement") >>= fromJSValUnchecked) -- | getLocation :: (MonadDOM m, IsDocument self) => self -> m (Maybe Location) getLocation self = liftDOM (((toDocument self) ^. js "location") >>= fromJSVal) -- | getLocationUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m Location getLocationUnsafe self = liftDOM ((((toDocument self) ^. js "location") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getLocationUnchecked :: (MonadDOM m, IsDocument self) => self -> m Location getLocationUnchecked self = liftDOM (((toDocument self) ^. js "location") >>= fromJSValUnchecked) -- | setDomain :: (MonadDOM m, IsDocument self, ToJSString val) => self -> val -> m () setDomain self val = liftDOM ((toDocument self) ^. jss "domain" (toJSVal val)) -- | getDomain :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getDomain self = liftDOM (((toDocument self) ^. js "domain") >>= fromJSValUnchecked) -- | getReferrer :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getReferrer self = liftDOM (((toDocument self) ^. js "referrer") >>= fromJSValUnchecked) -- | setCookie :: (MonadDOM m, IsDocument self, ToJSString val) => self -> val -> m () setCookie self val = liftDOM ((toDocument self) ^. jss "cookie" (toJSVal val)) -- | getCookie :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getCookie self = liftDOM (((toDocument self) ^. js "cookie") >>= fromJSValUnchecked) -- | getLastModified :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getLastModified self = liftDOM (((toDocument self) ^. js "lastModified") >>= fromJSValUnchecked) -- | getReadyState :: (MonadDOM m, IsDocument self) => self -> m DocumentReadyState getReadyState self = liftDOM (((toDocument self) ^. js "readyState") >>= fromJSValUnchecked) -- | setTitle :: (MonadDOM m, IsDocument self, ToJSString val) => self -> val -> m () setTitle self val = liftDOM ((toDocument self) ^. jss "title" (toJSVal val)) -- | getTitle :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getTitle self = liftDOM (((toDocument self) ^. js "title") >>= fromJSValUnchecked) -- | setDir :: (MonadDOM m, IsDocument self, ToJSString val) => self -> val -> m () setDir self val = liftDOM ((toDocument self) ^. jss "dir" (toJSVal val)) -- | getDir :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getDir self = liftDOM (((toDocument self) ^. js "dir") >>= fromJSValUnchecked) -- | setBody :: (MonadDOM m, IsDocument self, IsHTMLElement val) => self -> Maybe val -> m () setBody self val = liftDOM ((toDocument self) ^. jss "body" (toJSVal val)) -- | getBody :: (MonadDOM m, IsDocument self) => self -> m (Maybe HTMLElement) getBody self = liftDOM (((toDocument self) ^. js "body") >>= fromJSVal) -- | getBodyUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m HTMLElement getBodyUnsafe self = liftDOM ((((toDocument self) ^. js "body") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getBodyUnchecked :: (MonadDOM m, IsDocument self) => self -> m HTMLElement getBodyUnchecked self = liftDOM (((toDocument self) ^. js "body") >>= fromJSValUnchecked) -- | getHead :: (MonadDOM m, IsDocument self) => self -> m (Maybe HTMLHeadElement) getHead self = liftDOM (((toDocument self) ^. js "head") >>= fromJSVal) -- | getHeadUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m HTMLHeadElement getHeadUnsafe self = liftDOM ((((toDocument self) ^. js "head") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getHeadUnchecked :: (MonadDOM m, IsDocument self) => self -> m HTMLHeadElement getHeadUnchecked self = liftDOM (((toDocument self) ^. js "head") >>= fromJSValUnchecked) -- | getImages :: (MonadDOM m, IsDocument self) => self -> m HTMLCollection getImages self = liftDOM (((toDocument self) ^. js "images") >>= fromJSValUnchecked) -- | getEmbeds :: (MonadDOM m, IsDocument self) => self -> m HTMLCollection getEmbeds self = liftDOM (((toDocument self) ^. js "embeds") >>= fromJSValUnchecked) -- | getPlugins :: (MonadDOM m, IsDocument self) => self -> m HTMLCollection getPlugins self = liftDOM (((toDocument self) ^. js "plugins") >>= fromJSValUnchecked) -- | getLinks :: (MonadDOM m, IsDocument self) => self -> m HTMLCollection getLinks self = liftDOM (((toDocument self) ^. js "links") >>= fromJSValUnchecked) -- | getForms :: (MonadDOM m, IsDocument self) => self -> m HTMLCollection getForms self = liftDOM (((toDocument self) ^. js "forms") >>= fromJSValUnchecked) -- | getScripts :: (MonadDOM m, IsDocument self) => self -> m HTMLCollection getScripts self = liftDOM (((toDocument self) ^. js "scripts") >>= fromJSValUnchecked) -- | getCurrentScript :: (MonadDOM m, IsDocument self) => self -> m (Maybe HTMLScriptElement) getCurrentScript self = liftDOM (((toDocument self) ^. js "currentScript") >>= fromJSVal) -- | getCurrentScriptUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m HTMLScriptElement getCurrentScriptUnsafe self = liftDOM ((((toDocument self) ^. js "currentScript") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getCurrentScriptUnchecked :: (MonadDOM m, IsDocument self) => self -> m HTMLScriptElement getCurrentScriptUnchecked self = liftDOM (((toDocument self) ^. js "currentScript") >>= fromJSValUnchecked) -- | getDefaultView :: (MonadDOM m, IsDocument self) => self -> m (Maybe Window) getDefaultView self = liftDOM (((toDocument self) ^. js "defaultView") >>= fromJSVal) -- | getDefaultViewUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m Window getDefaultViewUnsafe self = liftDOM ((((toDocument self) ^. js "defaultView") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getDefaultViewUnchecked :: (MonadDOM m, IsDocument self) => self -> m Window getDefaultViewUnchecked self = liftDOM (((toDocument self) ^. js "defaultView") >>= fromJSValUnchecked) -- | setDesignMode :: (MonadDOM m, IsDocument self, ToJSString val) => self -> val -> m () setDesignMode self val = liftDOM ((toDocument self) ^. jss "designMode" (toJSVal val)) -- | getDesignMode :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getDesignMode self = liftDOM (((toDocument self) ^. js "designMode") >>= fromJSValUnchecked) -- | readyStateChange :: (IsDocument self, IsEventTarget self) => EventName self Event readyStateChange = unsafeEventNameAsync (toJSString "readystatechange") -- | getStyleSheets :: (MonadDOM m, IsDocument self) => self -> m StyleSheetList getStyleSheets self = liftDOM (((toDocument self) ^. js "styleSheets") >>= fromJSValUnchecked) -- | getScrollingElement :: (MonadDOM m, IsDocument self) => self -> m (Maybe Element) getScrollingElement self = liftDOM (((toDocument self) ^. js "scrollingElement") >>= fromJSVal) -- | getScrollingElementUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m Element getScrollingElementUnsafe self = liftDOM ((((toDocument self) ^. js "scrollingElement") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getScrollingElementUnchecked :: (MonadDOM m, IsDocument self) => self -> m Element getScrollingElementUnchecked self = liftDOM (((toDocument self) ^. js "scrollingElement") >>= fromJSValUnchecked) -- | getWebkitFullscreenEnabled :: (MonadDOM m, IsDocument self) => self -> m Bool getWebkitFullscreenEnabled self = liftDOM (((toDocument self) ^. js "webkitFullscreenEnabled") >>= valToBool) -- | getWebkitFullscreenElement :: (MonadDOM m, IsDocument self) => self -> m (Maybe Element) getWebkitFullscreenElement self = liftDOM (((toDocument self) ^. js "webkitFullscreenElement") >>= fromJSVal) -- | getWebkitFullscreenElementUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m Element getWebkitFullscreenElementUnsafe self = liftDOM ((((toDocument self) ^. js "webkitFullscreenElement") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getWebkitFullscreenElementUnchecked :: (MonadDOM m, IsDocument self) => self -> m Element getWebkitFullscreenElementUnchecked self = liftDOM (((toDocument self) ^. js "webkitFullscreenElement") >>= fromJSValUnchecked) -- | getWebkitIsFullScreen :: (MonadDOM m, IsDocument self) => self -> m Bool getWebkitIsFullScreen self = liftDOM (((toDocument self) ^. js "webkitIsFullScreen") >>= valToBool) -- | getWebkitFullScreenKeyboardInputAllowed :: (MonadDOM m, IsDocument self) => self -> m Bool getWebkitFullScreenKeyboardInputAllowed self = liftDOM (((toDocument self) ^. js "webkitFullScreenKeyboardInputAllowed") >>= valToBool) -- | getWebkitCurrentFullScreenElement :: (MonadDOM m, IsDocument self) => self -> m Element getWebkitCurrentFullScreenElement self = liftDOM (((toDocument self) ^. js "webkitCurrentFullScreenElement") >>= fromJSValUnchecked) -- | webKitFullscreenChange :: (IsDocument self, IsEventTarget self) => EventName self Event webKitFullscreenChange = unsafeEventName (toJSString "webkitfullscreenchange") -- | webKitFullscreenError :: (IsDocument self, IsEventTarget self) => EventName self Event webKitFullscreenError = unsafeEventName (toJSString "webkitfullscreenerror") -- | pointerlockchange :: (IsDocument self, IsEventTarget self) => EventName self Event pointerlockchange = unsafeEventName (toJSString "pointerlockchange") -- | pointerlockerror :: (IsDocument self, IsEventTarget self) => EventName self Event pointerlockerror = unsafeEventName (toJSString "pointerlockerror") -- | getFonts :: (MonadDOM m, IsDocument self) => self -> m FontFaceSet getFonts self = liftDOM (((toDocument self) ^. js "fonts") >>= fromJSValUnchecked) -- | getHidden :: (MonadDOM m, IsDocument self) => self -> m Bool getHidden self = liftDOM (((toDocument self) ^. js "hidden") >>= valToBool) -- | getVisibilityState :: (MonadDOM m, IsDocument self) => self -> m VisibilityState getVisibilityState self = liftDOM (((toDocument self) ^. js "visibilityState") >>= fromJSValUnchecked) -- | visibilitychange :: (IsDocument self, IsEventTarget self) => EventName self Event visibilitychange = unsafeEventName (toJSString "visibilitychange") -- | getApplets :: (MonadDOM m, IsDocument self) => self -> m HTMLCollection getApplets self = liftDOM (((toDocument self) ^. js "applets") >>= fromJSValUnchecked) -- | getAnchors :: (MonadDOM m, IsDocument self) => self -> m HTMLCollection getAnchors self = liftDOM (((toDocument self) ^. js "anchors") >>= fromJSValUnchecked) -- | getPreferredStylesheetSet :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m (Maybe result) getPreferredStylesheetSet self = liftDOM (((toDocument self) ^. js "preferredStylesheetSet") >>= fromMaybeJSString) -- | getPreferredStylesheetSetUnsafe :: (MonadDOM m, IsDocument self, HasCallStack, FromJSString result) => self -> m result getPreferredStylesheetSetUnsafe self = liftDOM ((((toDocument self) ^. js "preferredStylesheetSet") >>= fromMaybeJSString) >>= maybe (Prelude.error "Nothing to return") return) -- | getPreferredStylesheetSetUnchecked :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getPreferredStylesheetSetUnchecked self = liftDOM (((toDocument self) ^. js "preferredStylesheetSet") >>= fromJSValUnchecked) -- | setSelectedStylesheetSet :: (MonadDOM m, IsDocument self, ToJSString val) => self -> Maybe val -> m () setSelectedStylesheetSet self val = liftDOM ((toDocument self) ^. jss "selectedStylesheetSet" (toJSVal val)) -- | getSelectedStylesheetSet :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m (Maybe result) getSelectedStylesheetSet self = liftDOM (((toDocument self) ^. js "selectedStylesheetSet") >>= fromMaybeJSString) -- | getSelectedStylesheetSetUnsafe :: (MonadDOM m, IsDocument self, HasCallStack, FromJSString result) => self -> m result getSelectedStylesheetSetUnsafe self = liftDOM ((((toDocument self) ^. js "selectedStylesheetSet") >>= fromMaybeJSString) >>= maybe (Prelude.error "Nothing to return") return) -- | getSelectedStylesheetSetUnchecked :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getSelectedStylesheetSetUnchecked self = liftDOM (((toDocument self) ^. js "selectedStylesheetSet") >>= fromJSValUnchecked) -- | getXmlEncoding :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m (Maybe result) getXmlEncoding self = liftDOM (((toDocument self) ^. js "xmlEncoding") >>= fromMaybeJSString) -- | getXmlEncodingUnsafe :: (MonadDOM m, IsDocument self, HasCallStack, FromJSString result) => self -> m result getXmlEncodingUnsafe self = liftDOM ((((toDocument self) ^. js "xmlEncoding") >>= fromMaybeJSString) >>= maybe (Prelude.error "Nothing to return") return) -- | getXmlEncodingUnchecked :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getXmlEncodingUnchecked self = liftDOM (((toDocument self) ^. js "xmlEncoding") >>= fromJSValUnchecked) -- | setXmlVersion :: (MonadDOM m, IsDocument self, ToJSString val) => self -> Maybe val -> m () setXmlVersion self val = liftDOM ((toDocument self) ^. jss "xmlVersion" (toJSVal val)) -- | getXmlVersion :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m (Maybe result) getXmlVersion self = liftDOM (((toDocument self) ^. js "xmlVersion") >>= fromMaybeJSString) -- | getXmlVersionUnsafe :: (MonadDOM m, IsDocument self, HasCallStack, FromJSString result) => self -> m result getXmlVersionUnsafe self = liftDOM ((((toDocument self) ^. js "xmlVersion") >>= fromMaybeJSString) >>= maybe (Prelude.error "Nothing to return") return) -- | getXmlVersionUnchecked :: (MonadDOM m, IsDocument self, FromJSString result) => self -> m result getXmlVersionUnchecked self = liftDOM (((toDocument self) ^. js "xmlVersion") >>= fromJSValUnchecked) -- | setXmlStandalone :: (MonadDOM m, IsDocument self) => self -> Bool -> m () setXmlStandalone self val = liftDOM ((toDocument self) ^. jss "xmlStandalone" (toJSVal val)) -- | getXmlStandalone :: (MonadDOM m, IsDocument self) => self -> m Bool getXmlStandalone self = liftDOM (((toDocument self) ^. js "xmlStandalone") >>= valToBool) -- | selectStart :: (IsDocument self, IsEventTarget self) => EventName self Event selectStart = unsafeEventName (toJSString "selectstart") -- | selectionchange :: (IsDocument self, IsEventTarget self) => EventName self onselectionchange selectionchange = unsafeEventName (toJSString "selectionchange") -- | getRootElement :: (MonadDOM m, IsDocument self) => self -> m (Maybe SVGSVGElement) getRootElement self = liftDOM (((toDocument self) ^. js "rootElement") >>= fromJSVal) -- | getRootElementUnsafe :: (MonadDOM m, IsDocument self, HasCallStack) => self -> m SVGSVGElement getRootElementUnsafe self = liftDOM ((((toDocument self) ^. js "rootElement") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getRootElementUnchecked :: (MonadDOM m, IsDocument self) => self -> m SVGSVGElement getRootElementUnchecked self = liftDOM (((toDocument self) ^. js "rootElement") >>= fromJSValUnchecked)