module JSDOM.Generated.Range
(newRange, setStart, setEnd, setStartBefore, setStartAfter,
setEndBefore, setEndAfter, collapse, expand, selectNode,
selectNodeContents, compareBoundaryPoints, compareBoundaryPoints_,
deleteContents, extractContents, extractContents_, cloneContents,
cloneContents_, insertNode, surroundContents, cloneRange,
cloneRange_, toString, toString_, detach, getClientRects,
getClientRects_, getBoundingClientRect, getBoundingClientRect_,
createContextualFragment, createContextualFragment_, compareNode,
compareNode_, intersectsNode, intersectsNode_, comparePoint,
comparePoint_, isPointInRange, isPointInRange_,
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, 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 refNode) => Range -> refNode -> Word -> m ()
setStart self refNode offset
= liftDOM
(void (self ^. jsf "setStart" [toJSVal refNode, toJSVal offset]))
setEnd ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> Word -> m ()
setEnd self refNode offset
= liftDOM
(void (self ^. jsf "setEnd" [toJSVal refNode, toJSVal offset]))
setStartBefore ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m ()
setStartBefore self refNode
= liftDOM (void (self ^. jsf "setStartBefore" [toJSVal refNode]))
setStartAfter ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m ()
setStartAfter self refNode
= liftDOM (void (self ^. jsf "setStartAfter" [toJSVal refNode]))
setEndBefore ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m ()
setEndBefore self refNode
= liftDOM (void (self ^. jsf "setEndBefore" [toJSVal refNode]))
setEndAfter ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m ()
setEndAfter self refNode
= liftDOM (void (self ^. jsf "setEndAfter" [toJSVal refNode]))
collapse :: (MonadDOM m) => Range -> Bool -> m ()
collapse self toStart
= liftDOM (void (self ^. jsf "collapse" [toJSVal toStart]))
expand ::
(MonadDOM m, ToJSString unit) => Range -> Maybe unit -> m ()
expand self unit
= liftDOM (void (self ^. jsf "expand" [toJSVal unit]))
selectNode ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m ()
selectNode self refNode
= liftDOM (void (self ^. jsf "selectNode" [toJSVal refNode]))
selectNodeContents ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m ()
selectNodeContents self refNode
= liftDOM
(void (self ^. jsf "selectNodeContents" [toJSVal refNode]))
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 newNode) => Range -> newNode -> m ()
insertNode self newNode
= liftDOM (void (self ^. jsf "insertNode" [toJSVal newNode]))
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" ()))
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" ()))
detach :: (MonadDOM m) => Range -> m ()
detach self = liftDOM (void (self ^. jsf "detach" ()))
getClientRects :: (MonadDOM m) => Range -> m ClientRectList
getClientRects self
= liftDOM
((self ^. jsf "getClientRects" ()) >>= fromJSValUnchecked)
getClientRects_ :: (MonadDOM m) => Range -> m ()
getClientRects_ self
= liftDOM (void (self ^. jsf "getClientRects" ()))
getBoundingClientRect :: (MonadDOM m) => Range -> m ClientRect
getBoundingClientRect self
= liftDOM
((self ^. jsf "getBoundingClientRect" ()) >>= fromJSValUnchecked)
getBoundingClientRect_ :: (MonadDOM m) => Range -> m ()
getBoundingClientRect_ self
= liftDOM (void (self ^. jsf "getBoundingClientRect" ()))
createContextualFragment ::
(MonadDOM m, ToJSString html) =>
Range -> html -> m DocumentFragment
createContextualFragment self html
= liftDOM
((self ^. jsf "createContextualFragment" [toJSVal html]) >>=
fromJSValUnchecked)
createContextualFragment_ ::
(MonadDOM m, ToJSString html) => Range -> html -> m ()
createContextualFragment_ self html
= liftDOM
(void (self ^. jsf "createContextualFragment" [toJSVal html]))
compareNode ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m Int
compareNode self refNode
= liftDOM
(round <$>
((self ^. jsf "compareNode" [toJSVal refNode]) >>= valToNumber))
compareNode_ ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m ()
compareNode_ self refNode
= liftDOM (void (self ^. jsf "compareNode" [toJSVal refNode]))
intersectsNode ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m Bool
intersectsNode self refNode
= liftDOM
((self ^. jsf "intersectsNode" [toJSVal refNode]) >>= valToBool)
intersectsNode_ ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> m ()
intersectsNode_ self refNode
= liftDOM (void (self ^. jsf "intersectsNode" [toJSVal refNode]))
comparePoint ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> Word -> m Int
comparePoint self refNode offset
= liftDOM
(round <$>
((self ^. jsf "comparePoint" [toJSVal refNode, toJSVal offset]) >>=
valToNumber))
comparePoint_ ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> Word -> m ()
comparePoint_ self refNode offset
= liftDOM
(void
(self ^. jsf "comparePoint" [toJSVal refNode, toJSVal offset]))
isPointInRange ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> Word -> m Bool
isPointInRange self refNode offset
= liftDOM
((self ^. jsf "isPointInRange" [toJSVal refNode, toJSVal offset])
>>= valToBool)
isPointInRange_ ::
(MonadDOM m, IsNode refNode) => Range -> refNode -> Word -> m ()
isPointInRange_ self refNode offset
= liftDOM
(void
(self ^. jsf "isPointInRange" [toJSVal refNode, toJSVal offset]))
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)