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