{-# LANGUAGE PatternSynonyms #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} module JSDOM.Generated.Event (newEvent, composedPath, composedPath_, stopPropagation, stopImmediatePropagation, preventDefault, initEvent, pattern NONE, pattern CAPTURING_PHASE, pattern AT_TARGET, pattern BUBBLING_PHASE, getType, getTarget, getTargetUnsafe, getTargetUnchecked, getCurrentTarget, getCurrentTargetUnsafe, getCurrentTargetUnchecked, getEventPhase, setCancelBubble, getCancelBubble, getBubbles, getCancelable, getDefaultPrevented, getComposed, getIsTrusted, getTimeStamp, getSrcElement, setReturnValue, getReturnValue, Event(..), gTypeEvent, IsEvent, toEvent) 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.Enums -- | newEvent :: (MonadDOM m, ToJSString type', IsEventInit eventInitDict) => type' -> Maybe eventInitDict -> m Event newEvent type' eventInitDict = liftDOM (Event <$> new (jsg "Event") [toJSVal type', toJSVal eventInitDict]) -- | composedPath :: (MonadDOM m, IsEvent self) => self -> m [EventTarget] composedPath self = liftDOM (((toEvent self) ^. jsf "composedPath" ()) >>= fromJSArrayUnchecked) -- | composedPath_ :: (MonadDOM m, IsEvent self) => self -> m () composedPath_ self = liftDOM (void ((toEvent self) ^. jsf "composedPath" ())) -- | stopPropagation :: (MonadDOM m, IsEvent self) => self -> m () stopPropagation self = liftDOM (void ((toEvent self) ^. jsf "stopPropagation" ())) -- | stopImmediatePropagation :: (MonadDOM m, IsEvent self) => self -> m () stopImmediatePropagation self = liftDOM (void ((toEvent self) ^. jsf "stopImmediatePropagation" ())) -- | preventDefault :: (MonadDOM m, IsEvent self) => self -> m () preventDefault self = liftDOM (void ((toEvent self) ^. jsf "preventDefault" ())) -- | initEvent :: (MonadDOM m, IsEvent self, ToJSString type') => self -> type' -> Bool -> Bool -> m () initEvent self type' bubbles cancelable = liftDOM (void ((toEvent self) ^. jsf "initEvent" [toJSVal type', toJSVal bubbles, toJSVal cancelable])) pattern NONE = 0 pattern CAPTURING_PHASE = 1 pattern AT_TARGET = 2 pattern BUBBLING_PHASE = 3 -- | getType :: (MonadDOM m, IsEvent self, FromJSString result) => self -> m result getType self = liftDOM (((toEvent self) ^. js "type") >>= fromJSValUnchecked) -- | getTarget :: (MonadDOM m, IsEvent self) => self -> m (Maybe EventTarget) getTarget self = liftDOM (((toEvent self) ^. js "target") >>= fromJSVal) -- | getTargetUnsafe :: (MonadDOM m, IsEvent self, HasCallStack) => self -> m EventTarget getTargetUnsafe self = liftDOM ((((toEvent self) ^. js "target") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getTargetUnchecked :: (MonadDOM m, IsEvent self) => self -> m EventTarget getTargetUnchecked self = liftDOM (((toEvent self) ^. js "target") >>= fromJSValUnchecked) -- | getCurrentTarget :: (MonadDOM m, IsEvent self) => self -> m (Maybe EventTarget) getCurrentTarget self = liftDOM (((toEvent self) ^. js "currentTarget") >>= fromJSVal) -- | getCurrentTargetUnsafe :: (MonadDOM m, IsEvent self, HasCallStack) => self -> m EventTarget getCurrentTargetUnsafe self = liftDOM ((((toEvent self) ^. js "currentTarget") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getCurrentTargetUnchecked :: (MonadDOM m, IsEvent self) => self -> m EventTarget getCurrentTargetUnchecked self = liftDOM (((toEvent self) ^. js "currentTarget") >>= fromJSValUnchecked) -- | getEventPhase :: (MonadDOM m, IsEvent self) => self -> m Word getEventPhase self = liftDOM (round <$> (((toEvent self) ^. js "eventPhase") >>= valToNumber)) -- | setCancelBubble :: (MonadDOM m, IsEvent self) => self -> Bool -> m () setCancelBubble self val = liftDOM ((toEvent self) ^. jss "cancelBubble" (toJSVal val)) -- | getCancelBubble :: (MonadDOM m, IsEvent self) => self -> m Bool getCancelBubble self = liftDOM (((toEvent self) ^. js "cancelBubble") >>= valToBool) -- | getBubbles :: (MonadDOM m, IsEvent self) => self -> m Bool getBubbles self = liftDOM (((toEvent self) ^. js "bubbles") >>= valToBool) -- | getCancelable :: (MonadDOM m, IsEvent self) => self -> m Bool getCancelable self = liftDOM (((toEvent self) ^. js "cancelable") >>= valToBool) -- | getDefaultPrevented :: (MonadDOM m, IsEvent self) => self -> m Bool getDefaultPrevented self = liftDOM (((toEvent self) ^. js "defaultPrevented") >>= valToBool) -- | getComposed :: (MonadDOM m, IsEvent self) => self -> m Bool getComposed self = liftDOM (((toEvent self) ^. js "composed") >>= valToBool) -- | getIsTrusted :: (MonadDOM m, IsEvent self) => self -> m Bool getIsTrusted self = liftDOM (((toEvent self) ^. js "isTrusted") >>= valToBool) -- | getTimeStamp :: (MonadDOM m, IsEvent self) => self -> m Word getTimeStamp self = liftDOM (round <$> (((toEvent self) ^. js "timeStamp") >>= valToNumber)) -- | getSrcElement :: (MonadDOM m, IsEvent self) => self -> m EventTarget getSrcElement self = liftDOM (((toEvent self) ^. js "srcElement") >>= fromJSValUnchecked) -- | setReturnValue :: (MonadDOM m, IsEvent self) => self -> Bool -> m () setReturnValue self val = liftDOM ((toEvent self) ^. jss "returnValue" (toJSVal val)) -- | getReturnValue :: (MonadDOM m, IsEvent self) => self -> m Bool getReturnValue self = liftDOM (((toEvent self) ^. js "returnValue") >>= valToBool)