{-# LANGUAGE PatternSynonyms #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} module JSDOM.Generated.Range (newRange, setStart, setEnd, setStartBefore, setStartAfter, setEndBefore, setEndAfter, collapse, selectNode, selectNodeContents, compareBoundaryPoints, compareBoundaryPoints_, deleteContents, extractContents, extractContents_, extractContentsUnsafe, extractContentsUnchecked, cloneContents, cloneContents_, cloneContentsUnsafe, cloneContentsUnchecked, insertNode, surroundContents, cloneRange, cloneRange_, cloneRangeUnsafe, cloneRangeUnchecked, toString, toString_, detach, getClientRects, getClientRects_, getClientRectsUnsafe, getClientRectsUnchecked, getBoundingClientRect, getBoundingClientRect_, getBoundingClientRectUnsafe, getBoundingClientRectUnchecked, createContextualFragment, createContextualFragment_, createContextualFragmentUnsafe, createContextualFragmentUnchecked, intersectsNode, intersectsNode_, compareNode, compareNode_, comparePoint, comparePoint_, isPointInRange, isPointInRange_, expand, 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, getStartContainerUnsafe, getStartContainerUnchecked, getStartOffset, getEndContainer, getEndContainerUnsafe, getEndContainerUnchecked, getEndOffset, getCollapsed, getCommonAncestorContainer, getCommonAncestorContainerUnsafe, getCommonAncestorContainerUnchecked, 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 Language.Javascript.JSaddle (JSM(..), JSVal(..), JSString, strictEqual, toJSVal, valToStr, valToNumber, valToBool, js, jss, jsf, jsg, function, new, array) 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 -> Maybe refNode -> Int -> m () setStart self refNode offset = liftDOM (void (self ^. jsf "setStart" [toJSVal refNode, toJSVal offset])) -- | setEnd :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> Int -> m () setEnd self refNode offset = liftDOM (void (self ^. jsf "setEnd" [toJSVal refNode, toJSVal offset])) -- | setStartBefore :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m () setStartBefore self refNode = liftDOM (void (self ^. jsf "setStartBefore" [toJSVal refNode])) -- | setStartAfter :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m () setStartAfter self refNode = liftDOM (void (self ^. jsf "setStartAfter" [toJSVal refNode])) -- | setEndBefore :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m () setEndBefore self refNode = liftDOM (void (self ^. jsf "setEndBefore" [toJSVal refNode])) -- | setEndAfter :: (MonadDOM m, IsNode refNode) => Range -> Maybe 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])) -- | selectNode :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m () selectNode self refNode = liftDOM (void (self ^. jsf "selectNode" [toJSVal refNode])) -- | selectNodeContents :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m () selectNodeContents self refNode = liftDOM (void (self ^. jsf "selectNodeContents" [toJSVal refNode])) -- | compareBoundaryPoints :: (MonadDOM m) => Range -> Word -> Maybe Range -> m Int compareBoundaryPoints self how sourceRange = liftDOM (round <$> ((self ^. jsf "compareBoundaryPoints" [toJSVal how, toJSVal sourceRange]) >>= valToNumber)) -- | compareBoundaryPoints_ :: (MonadDOM m) => Range -> Word -> Maybe 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 (Maybe DocumentFragment) extractContents self = liftDOM ((self ^. jsf "extractContents" ()) >>= fromJSVal) -- | extractContents_ :: (MonadDOM m) => Range -> m () extractContents_ self = liftDOM (void (self ^. jsf "extractContents" ())) -- | extractContentsUnsafe :: (MonadDOM m, HasCallStack) => Range -> m DocumentFragment extractContentsUnsafe self = liftDOM (((self ^. jsf "extractContents" ()) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | extractContentsUnchecked :: (MonadDOM m) => Range -> m DocumentFragment extractContentsUnchecked self = liftDOM ((self ^. jsf "extractContents" ()) >>= fromJSValUnchecked) -- | cloneContents :: (MonadDOM m) => Range -> m (Maybe DocumentFragment) cloneContents self = liftDOM ((self ^. jsf "cloneContents" ()) >>= fromJSVal) -- | cloneContents_ :: (MonadDOM m) => Range -> m () cloneContents_ self = liftDOM (void (self ^. jsf "cloneContents" ())) -- | cloneContentsUnsafe :: (MonadDOM m, HasCallStack) => Range -> m DocumentFragment cloneContentsUnsafe self = liftDOM (((self ^. jsf "cloneContents" ()) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | cloneContentsUnchecked :: (MonadDOM m) => Range -> m DocumentFragment cloneContentsUnchecked self = liftDOM ((self ^. jsf "cloneContents" ()) >>= fromJSValUnchecked) -- | insertNode :: (MonadDOM m, IsNode newNode) => Range -> Maybe newNode -> m () insertNode self newNode = liftDOM (void (self ^. jsf "insertNode" [toJSVal newNode])) -- | surroundContents :: (MonadDOM m, IsNode newParent) => Range -> Maybe newParent -> m () surroundContents self newParent = liftDOM (void (self ^. jsf "surroundContents" [toJSVal newParent])) -- | cloneRange :: (MonadDOM m) => Range -> m (Maybe Range) cloneRange self = liftDOM ((self ^. jsf "cloneRange" ()) >>= fromJSVal) -- | cloneRange_ :: (MonadDOM m) => Range -> m () cloneRange_ self = liftDOM (void (self ^. jsf "cloneRange" ())) -- | cloneRangeUnsafe :: (MonadDOM m, HasCallStack) => Range -> m Range cloneRangeUnsafe self = liftDOM (((self ^. jsf "cloneRange" ()) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | cloneRangeUnchecked :: (MonadDOM m) => Range -> m Range cloneRangeUnchecked self = liftDOM ((self ^. jsf "cloneRange" ()) >>= fromJSValUnchecked) -- | 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 (Maybe ClientRectList) getClientRects self = liftDOM ((self ^. jsf "getClientRects" ()) >>= fromJSVal) -- | getClientRects_ :: (MonadDOM m) => Range -> m () getClientRects_ self = liftDOM (void (self ^. jsf "getClientRects" ())) -- | getClientRectsUnsafe :: (MonadDOM m, HasCallStack) => Range -> m ClientRectList getClientRectsUnsafe self = liftDOM (((self ^. jsf "getClientRects" ()) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getClientRectsUnchecked :: (MonadDOM m) => Range -> m ClientRectList getClientRectsUnchecked self = liftDOM ((self ^. jsf "getClientRects" ()) >>= fromJSValUnchecked) -- | getBoundingClientRect :: (MonadDOM m) => Range -> m (Maybe ClientRect) getBoundingClientRect self = liftDOM ((self ^. jsf "getBoundingClientRect" ()) >>= fromJSVal) -- | getBoundingClientRect_ :: (MonadDOM m) => Range -> m () getBoundingClientRect_ self = liftDOM (void (self ^. jsf "getBoundingClientRect" ())) -- | getBoundingClientRectUnsafe :: (MonadDOM m, HasCallStack) => Range -> m ClientRect getBoundingClientRectUnsafe self = liftDOM (((self ^. jsf "getBoundingClientRect" ()) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getBoundingClientRectUnchecked :: (MonadDOM m) => Range -> m ClientRect getBoundingClientRectUnchecked self = liftDOM ((self ^. jsf "getBoundingClientRect" ()) >>= fromJSValUnchecked) -- | createContextualFragment :: (MonadDOM m, ToJSString html) => Range -> html -> m (Maybe DocumentFragment) createContextualFragment self html = liftDOM ((self ^. jsf "createContextualFragment" [toJSVal html]) >>= fromJSVal) -- | createContextualFragment_ :: (MonadDOM m, ToJSString html) => Range -> html -> m () createContextualFragment_ self html = liftDOM (void (self ^. jsf "createContextualFragment" [toJSVal html])) -- | createContextualFragmentUnsafe :: (MonadDOM m, ToJSString html, HasCallStack) => Range -> html -> m DocumentFragment createContextualFragmentUnsafe self html = liftDOM (((self ^. jsf "createContextualFragment" [toJSVal html]) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | createContextualFragmentUnchecked :: (MonadDOM m, ToJSString html) => Range -> html -> m DocumentFragment createContextualFragmentUnchecked self html = liftDOM ((self ^. jsf "createContextualFragment" [toJSVal html]) >>= fromJSValUnchecked) -- | intersectsNode :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m Bool intersectsNode self refNode = liftDOM ((self ^. jsf "intersectsNode" [toJSVal refNode]) >>= valToBool) -- | intersectsNode_ :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m () intersectsNode_ self refNode = liftDOM (void (self ^. jsf "intersectsNode" [toJSVal refNode])) -- | compareNode :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m Int compareNode self refNode = liftDOM (round <$> ((self ^. jsf "compareNode" [toJSVal refNode]) >>= valToNumber)) -- | compareNode_ :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> m () compareNode_ self refNode = liftDOM (void (self ^. jsf "compareNode" [toJSVal refNode])) -- | comparePoint :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> Int -> m Int comparePoint self refNode offset = liftDOM (round <$> ((self ^. jsf "comparePoint" [toJSVal refNode, toJSVal offset]) >>= valToNumber)) -- | comparePoint_ :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> Int -> m () comparePoint_ self refNode offset = liftDOM (void (self ^. jsf "comparePoint" [toJSVal refNode, toJSVal offset])) -- | isPointInRange :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> Int -> m Bool isPointInRange self refNode offset = liftDOM ((self ^. jsf "isPointInRange" [toJSVal refNode, toJSVal offset]) >>= valToBool) -- | isPointInRange_ :: (MonadDOM m, IsNode refNode) => Range -> Maybe refNode -> Int -> m () isPointInRange_ self refNode offset = liftDOM (void (self ^. jsf "isPointInRange" [toJSVal refNode, toJSVal offset])) -- | expand :: (MonadDOM m, ToJSString unit) => Range -> unit -> m () expand self unit = liftDOM (void (self ^. jsf "expand" [toJSVal unit])) 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 (Maybe Node) getStartContainer self = liftDOM ((self ^. js "startContainer") >>= fromJSVal) -- | getStartContainerUnsafe :: (MonadDOM m, HasCallStack) => Range -> m Node getStartContainerUnsafe self = liftDOM (((self ^. js "startContainer") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getStartContainerUnchecked :: (MonadDOM m) => Range -> m Node getStartContainerUnchecked 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 (Maybe Node) getEndContainer self = liftDOM ((self ^. js "endContainer") >>= fromJSVal) -- | getEndContainerUnsafe :: (MonadDOM m, HasCallStack) => Range -> m Node getEndContainerUnsafe self = liftDOM (((self ^. js "endContainer") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getEndContainerUnchecked :: (MonadDOM m) => Range -> m Node getEndContainerUnchecked 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 (Maybe Node) getCommonAncestorContainer self = liftDOM ((self ^. js "commonAncestorContainer") >>= fromJSVal) -- | getCommonAncestorContainerUnsafe :: (MonadDOM m, HasCallStack) => Range -> m Node getCommonAncestorContainerUnsafe self = liftDOM (((self ^. js "commonAncestorContainer") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getCommonAncestorContainerUnchecked :: (MonadDOM m) => Range -> m Node getCommonAncestorContainerUnchecked self = liftDOM ((self ^. js "commonAncestorContainer") >>= fromJSValUnchecked)