{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.Selection
(collapse, collapseToEnd, collapseToStart, deleteFromDocument,
containsNode, containsNode_, selectAllChildren, extend, getRangeAt,
getRangeAt_, removeAllRanges, addRange, toString, toString_,
setBaseAndExtent, setPosition, empty, modify, getAnchorNode,
getAnchorNodeUnsafe, getAnchorNodeUnchecked, getAnchorOffset,
getFocusNode, getFocusNodeUnsafe, getFocusNodeUnchecked,
getFocusOffset, getIsCollapsed, getRangeCount, getType,
getBaseNode, getBaseNodeUnsafe, getBaseNodeUnchecked,
getBaseOffset, getExtentNode, getExtentNodeUnsafe,
getExtentNodeUnchecked, getExtentOffset, Selection(..),
gTypeSelection)
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
collapse ::
(MonadDOM m, IsNode node) =>
Selection -> Maybe node -> Maybe Word -> m ()
collapse self node offset
= liftDOM
(void (self ^. jsf "collapse" [toJSVal node, toJSVal offset]))
collapseToEnd :: (MonadDOM m) => Selection -> m ()
collapseToEnd self
= liftDOM (void (self ^. jsf "collapseToEnd" ()))
collapseToStart :: (MonadDOM m) => Selection -> m ()
collapseToStart self
= liftDOM (void (self ^. jsf "collapseToStart" ()))
deleteFromDocument :: (MonadDOM m) => Selection -> m ()
deleteFromDocument self
= liftDOM (void (self ^. jsf "deleteFromDocument" ()))
containsNode ::
(MonadDOM m, IsNode node) => Selection -> node -> Bool -> m Bool
containsNode self node allowPartial
= liftDOM
((self ^. jsf "containsNode" [toJSVal node, toJSVal allowPartial])
>>= valToBool)
containsNode_ ::
(MonadDOM m, IsNode node) => Selection -> node -> Bool -> m ()
containsNode_ self node allowPartial
= liftDOM
(void
(self ^. jsf "containsNode" [toJSVal node, toJSVal allowPartial]))
selectAllChildren ::
(MonadDOM m, IsNode node) => Selection -> node -> m ()
selectAllChildren self node
= liftDOM (void (self ^. jsf "selectAllChildren" [toJSVal node]))
extend ::
(MonadDOM m, IsNode node) =>
Selection -> node -> Maybe Word -> m ()
extend self node offset
= liftDOM
(void (self ^. jsf "extend" [toJSVal node, toJSVal offset]))
getRangeAt :: (MonadDOM m) => Selection -> Word -> m Range
getRangeAt self index
= liftDOM
((self ^. jsf "getRangeAt" [toJSVal index]) >>= fromJSValUnchecked)
getRangeAt_ :: (MonadDOM m) => Selection -> Word -> m ()
getRangeAt_ self index
= liftDOM (void (self ^. jsf "getRangeAt" [toJSVal index]))
removeAllRanges :: (MonadDOM m) => Selection -> m ()
removeAllRanges self
= liftDOM (void (self ^. jsf "removeAllRanges" ()))
addRange :: (MonadDOM m) => Selection -> Range -> m ()
addRange self range
= liftDOM (void (self ^. jsf "addRange" [toJSVal range]))
toString ::
(MonadDOM m, FromJSString result) => Selection -> m result
toString self
= liftDOM ((self ^. jsf "toString" ()) >>= fromJSValUnchecked)
toString_ :: (MonadDOM m) => Selection -> m ()
toString_ self = liftDOM (void (self ^. jsf "toString" ()))
setBaseAndExtent ::
(MonadDOM m, IsNode baseNode, IsNode extentNode) =>
Selection ->
Maybe baseNode -> Word -> Maybe extentNode -> Word -> m ()
setBaseAndExtent self baseNode baseOffset extentNode extentOffset
= liftDOM
(void
(self ^. jsf "setBaseAndExtent"
[toJSVal baseNode, toJSVal baseOffset, toJSVal extentNode,
toJSVal extentOffset]))
setPosition ::
(MonadDOM m, IsNode node) =>
Selection -> Maybe node -> Maybe Word -> m ()
setPosition self node offset
= liftDOM
(void (self ^. jsf "setPosition" [toJSVal node, toJSVal offset]))
empty :: (MonadDOM m) => Selection -> m ()
empty self = liftDOM (void (self ^. jsf "empty" ()))
modify ::
(MonadDOM m, ToJSString alter, ToJSString direction,
ToJSString granularity) =>
Selection ->
Maybe alter -> Maybe direction -> Maybe granularity -> m ()
modify self alter direction granularity
= liftDOM
(void
(self ^. jsf "modify"
[toJSVal alter, toJSVal direction, toJSVal granularity]))
getAnchorNode :: (MonadDOM m) => Selection -> m (Maybe Node)
getAnchorNode self
= liftDOM ((self ^. js "anchorNode") >>= fromJSVal)
getAnchorNodeUnsafe ::
(MonadDOM m, HasCallStack) => Selection -> m Node
getAnchorNodeUnsafe self
= liftDOM
(((self ^. js "anchorNode") >>= fromJSVal) >>=
maybe (Prelude.error "Nothing to return") return)
getAnchorNodeUnchecked :: (MonadDOM m) => Selection -> m Node
getAnchorNodeUnchecked self
= liftDOM ((self ^. js "anchorNode") >>= fromJSValUnchecked)
getAnchorOffset :: (MonadDOM m) => Selection -> m Word
getAnchorOffset self
= liftDOM (round <$> ((self ^. js "anchorOffset") >>= valToNumber))
getFocusNode :: (MonadDOM m) => Selection -> m (Maybe Node)
getFocusNode self
= liftDOM ((self ^. js "focusNode") >>= fromJSVal)
getFocusNodeUnsafe ::
(MonadDOM m, HasCallStack) => Selection -> m Node
getFocusNodeUnsafe self
= liftDOM
(((self ^. js "focusNode") >>= fromJSVal) >>=
maybe (Prelude.error "Nothing to return") return)
getFocusNodeUnchecked :: (MonadDOM m) => Selection -> m Node
getFocusNodeUnchecked self
= liftDOM ((self ^. js "focusNode") >>= fromJSValUnchecked)
getFocusOffset :: (MonadDOM m) => Selection -> m Word
getFocusOffset self
= liftDOM (round <$> ((self ^. js "focusOffset") >>= valToNumber))
getIsCollapsed :: (MonadDOM m) => Selection -> m Bool
getIsCollapsed self
= liftDOM ((self ^. js "isCollapsed") >>= valToBool)
getRangeCount :: (MonadDOM m) => Selection -> m Word
getRangeCount self
= liftDOM (round <$> ((self ^. js "rangeCount") >>= valToNumber))
getType ::
(MonadDOM m, FromJSString result) => Selection -> m result
getType self = liftDOM ((self ^. js "type") >>= fromJSValUnchecked)
getBaseNode :: (MonadDOM m) => Selection -> m (Maybe Node)
getBaseNode self = liftDOM ((self ^. js "baseNode") >>= fromJSVal)
getBaseNodeUnsafe ::
(MonadDOM m, HasCallStack) => Selection -> m Node
getBaseNodeUnsafe self
= liftDOM
(((self ^. js "baseNode") >>= fromJSVal) >>=
maybe (Prelude.error "Nothing to return") return)
getBaseNodeUnchecked :: (MonadDOM m) => Selection -> m Node
getBaseNodeUnchecked self
= liftDOM ((self ^. js "baseNode") >>= fromJSValUnchecked)
getBaseOffset :: (MonadDOM m) => Selection -> m Word
getBaseOffset self
= liftDOM (round <$> ((self ^. js "baseOffset") >>= valToNumber))
getExtentNode :: (MonadDOM m) => Selection -> m (Maybe Node)
getExtentNode self
= liftDOM ((self ^. js "extentNode") >>= fromJSVal)
getExtentNodeUnsafe ::
(MonadDOM m, HasCallStack) => Selection -> m Node
getExtentNodeUnsafe self
= liftDOM
(((self ^. js "extentNode") >>= fromJSVal) >>=
maybe (Prelude.error "Nothing to return") return)
getExtentNodeUnchecked :: (MonadDOM m) => Selection -> m Node
getExtentNodeUnchecked self
= liftDOM ((self ^. js "extentNode") >>= fromJSValUnchecked)
getExtentOffset :: (MonadDOM m) => Selection -> m Word
getExtentOffset self
= liftDOM (round <$> ((self ^. js "extentOffset") >>= valToNumber))