{-# LANGUAGE CPP #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE JavaScriptFFI #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} module GHCJS.DOM.JSFFI.Generated.UIEvent (js_initUIEvent, initUIEvent, js_getView, getView, getViewUnsafe, getViewUnchecked, js_getDetail, getDetail, js_getKeyCode, getKeyCode, js_getCharCode, getCharCode, js_getLayerX, getLayerX, js_getLayerY, getLayerY, js_getPageX, getPageX, js_getPageY, getPageY, js_getWhich, getWhich, UIEvent(..), gTypeUIEvent, IsUIEvent, toUIEvent) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, fmap, Show, Read, Eq, Ord) import qualified Prelude (error) import Data.Typeable (Typeable) import GHCJS.Types (JSVal(..), JSString) import GHCJS.Foreign (jsNull) import GHCJS.Foreign.Callback (syncCallback, asyncCallback, syncCallback1, asyncCallback1, syncCallback2, asyncCallback2, OnBlocked(..)) import GHCJS.Marshal (ToJSVal(..), FromJSVal(..)) import GHCJS.Marshal.Pure (PToJSVal(..), PFromJSVal(..)) import Control.Monad (void) import Control.Monad.IO.Class (MonadIO(..)) import Data.Int (Int64) import Data.Word (Word, Word64) import Data.Maybe (fromJust) import GHCJS.DOM.Types import Control.Applicative ((<$>)) import GHCJS.DOM.JSFFI.Generated.Enums #if MIN_VERSION_base(4,9,0) import GHC.Stack (HasCallStack) #elif MIN_VERSION_base(4,8,0) import GHC.Stack (CallStack) import GHC.Exts (Constraint) type HasCallStack = ((?callStack :: CallStack) :: Constraint) #else import GHC.Exts (Constraint) type HasCallStack = (() :: Constraint) #endif foreign import javascript unsafe "$1[\"initUIEvent\"]($2, $3, $4,\n$5, $6)" js_initUIEvent :: UIEvent -> JSString -> Bool -> Bool -> Nullable Window -> Int -> IO () -- | initUIEvent :: (MonadIO m, IsUIEvent self, ToJSString type') => self -> type' -> Bool -> Bool -> Maybe Window -> Int -> m () initUIEvent self type' canBubble cancelable view detail = liftIO (js_initUIEvent (toUIEvent self) (toJSString type') canBubble cancelable (maybeToNullable view) detail) foreign import javascript unsafe "$1[\"view\"]" js_getView :: UIEvent -> IO (Nullable Window) -- | getView :: (MonadIO m, IsUIEvent self) => self -> m (Maybe Window) getView self = liftIO (nullableToMaybe <$> (js_getView (toUIEvent self))) -- | getViewUnsafe :: (MonadIO m, IsUIEvent self, HasCallStack) => self -> m Window getViewUnsafe self = liftIO ((nullableToMaybe <$> (js_getView (toUIEvent self))) >>= maybe (Prelude.error "Nothing to return") return) -- | getViewUnchecked :: (MonadIO m, IsUIEvent self) => self -> m Window getViewUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getView (toUIEvent self))) foreign import javascript unsafe "$1[\"detail\"]" js_getDetail :: UIEvent -> IO Int -- | getDetail :: (MonadIO m, IsUIEvent self) => self -> m Int getDetail self = liftIO (js_getDetail (toUIEvent self)) foreign import javascript unsafe "$1[\"keyCode\"]" js_getKeyCode :: UIEvent -> IO Int -- | getKeyCode :: (MonadIO m, IsUIEvent self) => self -> m Int getKeyCode self = liftIO (js_getKeyCode (toUIEvent self)) foreign import javascript unsafe "$1[\"charCode\"]" js_getCharCode :: UIEvent -> IO Int -- | getCharCode :: (MonadIO m, IsUIEvent self) => self -> m Int getCharCode self = liftIO (js_getCharCode (toUIEvent self)) foreign import javascript unsafe "$1[\"layerX\"]" js_getLayerX :: UIEvent -> IO Int -- | getLayerX :: (MonadIO m, IsUIEvent self) => self -> m Int getLayerX self = liftIO (js_getLayerX (toUIEvent self)) foreign import javascript unsafe "$1[\"layerY\"]" js_getLayerY :: UIEvent -> IO Int -- | getLayerY :: (MonadIO m, IsUIEvent self) => self -> m Int getLayerY self = liftIO (js_getLayerY (toUIEvent self)) foreign import javascript unsafe "$1[\"pageX\"]" js_getPageX :: UIEvent -> IO Int -- | getPageX :: (MonadIO m, IsUIEvent self) => self -> m Int getPageX self = liftIO (js_getPageX (toUIEvent self)) foreign import javascript unsafe "$1[\"pageY\"]" js_getPageY :: UIEvent -> IO Int -- | getPageY :: (MonadIO m, IsUIEvent self) => self -> m Int getPageY self = liftIO (js_getPageY (toUIEvent self)) foreign import javascript unsafe "$1[\"which\"]" js_getWhich :: UIEvent -> IO Int -- | getWhich :: (MonadIO m, IsUIEvent self) => self -> m Int getWhich self = liftIO (js_getWhich (toUIEvent self))