module JSDOM.Generated.Range
(newRange, setStart, setEnd, setStartBefore, setStartAfter,
setEndBefore, setEndAfter, collapse, selectNode,
selectNodeContents, compareBoundaryPoints, compareBoundaryPoints_,
deleteContents, extractContents, extractContents_, cloneContents,
cloneContents_, insertNode, surroundContents, cloneRange,
cloneRange_, detach, isPointInRange, isPointInRange_, comparePoint,
comparePoint_, intersectsNode, intersectsNode_, toString,
toString_, getClientRects, getClientRects_, getBoundingClientRect,
getBoundingClientRect_, createContextualFragment,
createContextualFragment_, expand, compareNode, compareNode_,
pattern START_TO_START, pattern START_TO_END, pattern END_TO_END,
pattern END_TO_START, pattern NODE_BEFORE, pattern NODE_AFTER,
pattern NODE_BEFORE_AND_AFTER, pattern NODE_INSIDE,
getStartContainer, getStartOffset, getEndContainer, getEndOffset,
getCollapsed, getCommonAncestorContainer, Range(..), gTypeRange)
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)
import JSDOM.Enums
newRange :: (MonadDOM m) => m Range
newRange = liftDOM (Range <$> new (jsg "Range") ())
setStart ::
(MonadDOM m, IsNode node) => Range -> node -> Word -> m ()
setStart self node offset
= liftDOM
(void (self ^. jsf "setStart" [toJSVal node, toJSVal offset]))
setEnd ::
(MonadDOM m, IsNode node) => Range -> node -> Word -> m ()
setEnd self node offset
= liftDOM
(void (self ^. jsf "setEnd" [toJSVal node, toJSVal offset]))
setStartBefore ::
(MonadDOM m, IsNode node) => Range -> node -> m ()
setStartBefore self node
= liftDOM (void (self ^. jsf "setStartBefore" [toJSVal node]))
setStartAfter :: (MonadDOM m, IsNode node) => Range -> node -> m ()
setStartAfter self node
= liftDOM (void (self ^. jsf "setStartAfter" [toJSVal node]))
setEndBefore :: (MonadDOM m, IsNode node) => Range -> node -> m ()
setEndBefore self node
= liftDOM (void (self ^. jsf "setEndBefore" [toJSVal node]))
setEndAfter :: (MonadDOM m, IsNode node) => Range -> node -> m ()
setEndAfter self node
= liftDOM (void (self ^. jsf "setEndAfter" [toJSVal node]))
collapse :: (MonadDOM m) => Range -> Bool -> m ()
collapse self toStart
= liftDOM (void (self ^. jsf "collapse" [toJSVal toStart]))
selectNode :: (MonadDOM m, IsNode node) => Range -> node -> m ()
selectNode self node
= liftDOM (void (self ^. jsf "selectNode" [toJSVal node]))
selectNodeContents ::
(MonadDOM m, IsNode node) => Range -> node -> m ()
selectNodeContents self node
= liftDOM (void (self ^. jsf "selectNodeContents" [toJSVal node]))
compareBoundaryPoints ::
(MonadDOM m) => Range -> Word -> Range -> m Int
compareBoundaryPoints self how sourceRange
= liftDOM
(round <$>
((self ^. jsf "compareBoundaryPoints"
[toJSVal how, toJSVal sourceRange])
>>= valToNumber))
compareBoundaryPoints_ ::
(MonadDOM m) => Range -> Word -> Range -> m ()
compareBoundaryPoints_ self how sourceRange
= liftDOM
(void
(self ^. jsf "compareBoundaryPoints"
[toJSVal how, toJSVal sourceRange]))
deleteContents :: (MonadDOM m) => Range -> m ()
deleteContents self
= liftDOM (void (self ^. jsf "deleteContents" ()))
extractContents :: (MonadDOM m) => Range -> m DocumentFragment
extractContents self
= liftDOM
((self ^. jsf "extractContents" ()) >>= fromJSValUnchecked)
extractContents_ :: (MonadDOM m) => Range -> m ()
extractContents_ self
= liftDOM (void (self ^. jsf "extractContents" ()))
cloneContents :: (MonadDOM m) => Range -> m DocumentFragment
cloneContents self
= liftDOM ((self ^. jsf "cloneContents" ()) >>= fromJSValUnchecked)
cloneContents_ :: (MonadDOM m) => Range -> m ()
cloneContents_ self
= liftDOM (void (self ^. jsf "cloneContents" ()))
insertNode :: (MonadDOM m, IsNode node) => Range -> node -> m ()
insertNode self node
= liftDOM (void (self ^. jsf "insertNode" [toJSVal node]))
surroundContents ::
(MonadDOM m, IsNode newParent) => Range -> newParent -> m ()
surroundContents self newParent
= liftDOM
(void (self ^. jsf "surroundContents" [toJSVal newParent]))
cloneRange :: (MonadDOM m) => Range -> m Range
cloneRange self
= liftDOM ((self ^. jsf "cloneRange" ()) >>= fromJSValUnchecked)
cloneRange_ :: (MonadDOM m) => Range -> m ()
cloneRange_ self = liftDOM (void (self ^. jsf "cloneRange" ()))
detach :: (MonadDOM m) => Range -> m ()
detach self = liftDOM (void (self ^. jsf "detach" ()))
isPointInRange ::
(MonadDOM m, IsNode node) => Range -> node -> Word -> m Bool
isPointInRange self node offset
= liftDOM
((self ^. jsf "isPointInRange" [toJSVal node, toJSVal offset]) >>=
valToBool)
isPointInRange_ ::
(MonadDOM m, IsNode node) => Range -> node -> Word -> m ()
isPointInRange_ self node offset
= liftDOM
(void
(self ^. jsf "isPointInRange" [toJSVal node, toJSVal offset]))
comparePoint ::
(MonadDOM m, IsNode node) => Range -> node -> Word -> m Int
comparePoint self node offset
= liftDOM
(round <$>
((self ^. jsf "comparePoint" [toJSVal node, toJSVal offset]) >>=
valToNumber))
comparePoint_ ::
(MonadDOM m, IsNode node) => Range -> node -> Word -> m ()
comparePoint_ self node offset
= liftDOM
(void (self ^. jsf "comparePoint" [toJSVal node, toJSVal offset]))
intersectsNode ::
(MonadDOM m, IsNode node) => Range -> node -> m Bool
intersectsNode self node
= liftDOM
((self ^. jsf "intersectsNode" [toJSVal node]) >>= valToBool)
intersectsNode_ ::
(MonadDOM m, IsNode node) => Range -> node -> m ()
intersectsNode_ self node
= liftDOM (void (self ^. jsf "intersectsNode" [toJSVal node]))
toString :: (MonadDOM m, FromJSString result) => Range -> m result
toString self
= liftDOM ((self ^. jsf "toString" ()) >>= fromJSValUnchecked)
toString_ :: (MonadDOM m) => Range -> m ()
toString_ self = liftDOM (void (self ^. jsf "toString" ()))
getClientRects :: (MonadDOM m) => Range -> m [DOMRect]
getClientRects self
= liftDOM
((self ^. jsf "getClientRects" ()) >>= fromJSArrayUnchecked)
getClientRects_ :: (MonadDOM m) => Range -> m ()
getClientRects_ self
= liftDOM (void (self ^. jsf "getClientRects" ()))
getBoundingClientRect :: (MonadDOM m) => Range -> m DOMRect
getBoundingClientRect self
= liftDOM
((self ^. jsf "getBoundingClientRect" ()) >>= fromJSValUnchecked)
getBoundingClientRect_ :: (MonadDOM m) => Range -> m ()
getBoundingClientRect_ self
= liftDOM (void (self ^. jsf "getBoundingClientRect" ()))
createContextualFragment ::
(MonadDOM m, ToJSString fragment) =>
Range -> fragment -> m DocumentFragment
createContextualFragment self fragment
= liftDOM
((self ^. jsf "createContextualFragment" [toJSVal fragment]) >>=
fromJSValUnchecked)
createContextualFragment_ ::
(MonadDOM m, ToJSString fragment) => Range -> fragment -> m ()
createContextualFragment_ self fragment
= liftDOM
(void (self ^. jsf "createContextualFragment" [toJSVal fragment]))
expand ::
(MonadDOM m, ToJSString unit) => Range -> Maybe unit -> m ()
expand self unit
= liftDOM (void (self ^. jsf "expand" [toJSVal unit]))
compareNode :: (MonadDOM m, IsNode node) => Range -> node -> m Int
compareNode self node
= liftDOM
(round <$>
((self ^. jsf "compareNode" [toJSVal node]) >>= valToNumber))
compareNode_ :: (MonadDOM m, IsNode node) => Range -> node -> m ()
compareNode_ self node
= liftDOM (void (self ^. jsf "compareNode" [toJSVal node]))
pattern START_TO_START = 0
pattern START_TO_END = 1
pattern END_TO_END = 2
pattern END_TO_START = 3
pattern NODE_BEFORE = 0
pattern NODE_AFTER = 1
pattern NODE_BEFORE_AND_AFTER = 2
pattern NODE_INSIDE = 3
getStartContainer :: (MonadDOM m) => Range -> m Node
getStartContainer self
= liftDOM ((self ^. js "startContainer") >>= fromJSValUnchecked)
getStartOffset :: (MonadDOM m) => Range -> m Int
getStartOffset self
= liftDOM (round <$> ((self ^. js "startOffset") >>= valToNumber))
getEndContainer :: (MonadDOM m) => Range -> m Node
getEndContainer self
= liftDOM ((self ^. js "endContainer") >>= fromJSValUnchecked)
getEndOffset :: (MonadDOM m) => Range -> m Int
getEndOffset self
= liftDOM (round <$> ((self ^. js "endOffset") >>= valToNumber))
getCollapsed :: (MonadDOM m) => Range -> m Bool
getCollapsed self
= liftDOM ((self ^. js "collapsed") >>= valToBool)
getCommonAncestorContainer :: (MonadDOM m) => Range -> m Node
getCommonAncestorContainer self
= liftDOM
((self ^. js "commonAncestorContainer") >>= fromJSValUnchecked)