{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Miso.Html.Event
(
on
, onWithOptions
, onMounted
, onMountedWith
, onBeforeMounted
, onUnmounted
, onUnmountedWith
, onBeforeUnmounted
, onCreated
, onBeforeCreated
, onDestroyed
, onBeforeDestroyed
, onClick
, onClickWith
, onDoubleClick
, onMouseDown
, onMouseUp
, onMouseEnter
, onMouseLeave
, onMouseOver
, onMouseOut
, onKeyDown
, onKeyDownWithInfo
, onKeyPress
, onKeyUp
, onInput
, onChange
, onChangeWith
, onChecked
, onSubmit
, onBlur
, onFocus
, onDrag
, onDragLeave
, onDragEnter
, onDragEnd
, onDragStart
, onDragOver
, onDrop
, onSelect
, onPointerDown
, onPointerUp
, onPointerEnter
, onPointerLeave
, onPointerOver
, onPointerOut
, onPointerCancel
, onPointerMove
) where
import Control.Monad (when, forM_)
import qualified Data.Map.Strict as M
import Data.Aeson.Types (parseEither)
import Language.Javascript.JSaddle
import Miso.Event
import qualified Miso.FFI.Internal as FFI
import Miso.Types ( Attribute (Event), LogLevel(..) )
import Miso.String (MisoString, unpack)
on :: MisoString
-> Decoder r
-> (r -> JSVal -> action)
-> Attribute action
on :: forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on = Options
-> MisoString
-> Decoder r
-> (r -> JSVal -> action)
-> Attribute action
forall r action.
Options
-> MisoString
-> Decoder r
-> (r -> JSVal -> action)
-> Attribute action
onWithOptions Options
defaultOptions
onWithOptions
:: Options
-> MisoString
-> Decoder r
-> (r -> JSVal -> action)
-> Attribute action
onWithOptions :: forall r action.
Options
-> MisoString
-> Decoder r
-> (r -> JSVal -> action)
-> Attribute action
onWithOptions Options
options MisoString
eventName Decoder{DecodeTarget
Value -> Parser r
decoder :: Value -> Parser r
decodeAt :: DecodeTarget
decodeAt :: forall a. Decoder a -> DecodeTarget
decoder :: forall a. Decoder a -> Value -> Parser a
..} r -> JSVal -> action
toAction =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
n LogLevel
logLevel Events
events ->
case MisoString -> Events -> Maybe Capture
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup MisoString
eventName Events
events of
Maybe Capture
Nothing ->
Capture -> JSM () -> JSM ()
forall (f :: * -> *). Applicative f => Capture -> f () -> f ()
when (LogLevel
logLevel LogLevel -> [LogLevel] -> Capture
forall a. Eq a => a -> [a] -> Capture
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Capture
`elem` [ LogLevel
DebugAll, LogLevel
DebugEvents ]) (JSM () -> JSM ()) -> JSM () -> JSM ()
forall a b. (a -> b) -> a -> b
$
MisoString -> JSM ()
FFI.consoleWarn (MisoString -> JSM ()) -> MisoString -> JSM ()
forall a b. (a -> b) -> a -> b
$ [MisoString] -> MisoString
forall a. Monoid a => [a] -> a
mconcat
[ MisoString
"[DEBUG_EVENTS] \""
, MisoString
eventName
, MisoString
"\" is not being listened on. To use this event, "
, MisoString
"add to the 'events' @Map@ in @Component@"
]
Just Capture
_ -> do
eventObj <- JSString -> Object -> JSM JSVal
getProp JSString
"events" Object
n
eventHandlerObject@(Object eo) <- create
jsOptions <- toJSVal options
decodeAtVal <- toJSVal decodeAt
cb <- FFI.asyncCallback2 $ \JSVal
e JSVal
domRef -> do
Just v <- JSVal -> JSM (Maybe Value)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal (JSVal -> JSM (Maybe Value)) -> JSM JSVal -> JSM (Maybe Value)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< JSVal -> JSVal -> JSM JSVal
FFI.eventJSON JSVal
decodeAtVal JSVal
e
case parseEither decoder v of
Left [Char]
s -> [Char] -> JSM ()
forall a. HasCallStack => [Char] -> a
error ([Char] -> JSM ()) -> [Char] -> JSM ()
forall a b. (a -> b) -> a -> b
$ [Char]
"[ERROR] Parse error on " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> MisoString -> [Char]
unpack MisoString
eventName [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
": " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
s
Right r
r -> Sink action
sink (r -> JSVal -> action
toAction r
r JSVal
domRef)
FFI.set "runEvent" cb eventHandlerObject
FFI.set "options" jsOptions eventHandlerObject
FFI.set eventName eo (Object eventObj)
onMounted :: action -> Attribute action
onMounted :: forall action. action -> Attribute action
onMounted action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- JSM () -> JSM Function
FFI.syncCallback (Sink action
sink action
action)
FFI.set "onMounted" callback object
onMountedWith :: (MisoString -> action) -> Attribute action
onMountedWith :: forall action. (MisoString -> action) -> Attribute action
onMountedWith MisoString -> action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- (JSVal -> JSM ()) -> JSM Function
FFI.syncCallback1 ((JSVal -> JSM ()) -> JSM Function)
-> (JSVal -> JSM ()) -> JSM Function
forall a b. (a -> b) -> a -> b
$ \JSVal
jval -> do
maybeName <- JSVal -> JSM (Maybe MisoString)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal JSVal
jval
forM_ maybeName (sink . action)
FFI.set "onMounted" callback object
onBeforeMounted :: action -> Attribute action
onBeforeMounted :: forall action. action -> Attribute action
onBeforeMounted action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- JSM () -> JSM Function
FFI.syncCallback (Sink action
sink action
action)
FFI.set "onBeforeMounted" callback object
onCreated :: action -> Attribute action
onCreated :: forall action. action -> Attribute action
onCreated action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- JSM () -> JSM Function
FFI.syncCallback (Sink action
sink action
action)
FFI.set "onCreated" callback object
onDestroyed :: action -> Attribute action
onDestroyed :: forall action. action -> Attribute action
onDestroyed action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- JSM () -> JSM Function
FFI.syncCallback (Sink action
sink action
action)
FFI.set "onDestroyed" callback object
onUnmounted :: action -> Attribute action
onUnmounted :: forall action. action -> Attribute action
onUnmounted action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- JSM () -> JSM Function
FFI.syncCallback (Sink action
sink action
action)
FFI.set "onUnmounted" callback object
onUnmountedWith :: (MisoString -> action) -> Attribute action
onUnmountedWith :: forall action. (MisoString -> action) -> Attribute action
onUnmountedWith MisoString -> action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- (JSVal -> JSM ()) -> JSM Function
FFI.syncCallback1 ((JSVal -> JSM ()) -> JSM Function)
-> (JSVal -> JSM ()) -> JSM Function
forall a b. (a -> b) -> a -> b
$ \JSVal
jval -> do
maybeName <- JSVal -> JSM (Maybe MisoString)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal JSVal
jval
forM_ maybeName (sink . action)
FFI.set "onUnmounted" callback object
onBeforeUnmounted :: action -> Attribute action
onBeforeUnmounted :: forall action. action -> Attribute action
onBeforeUnmounted action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- JSM () -> JSM Function
FFI.syncCallback (Sink action
sink action
action)
FFI.set "onBeforeUnmounted" callback object
onBeforeDestroyed :: action -> Attribute action
onBeforeDestroyed :: forall action. action -> Attribute action
onBeforeDestroyed action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- JSM () -> JSM Function
FFI.syncCallback (Sink action
sink action
action)
FFI.set "onBeforeDestroyed" callback object
onBeforeCreated :: action -> Attribute action
onBeforeCreated :: forall action. action -> Attribute action
onBeforeCreated action
action =
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall action.
(Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
Event ((Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action)
-> (Sink action -> Object -> LogLevel -> Events -> JSM ())
-> Attribute action
forall a b. (a -> b) -> a -> b
$ \Sink action
sink Object
object LogLevel
_ Events
_ -> do
callback <- JSM () -> JSM Function
FFI.syncCallback (Sink action
sink action
action)
FFI.set "onBeforeCreated" callback object
onBlur :: action -> Attribute action
onBlur :: forall action. action -> Attribute action
onBlur action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"blur" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onChecked :: (Checked -> action) -> Attribute action
onChecked :: forall action. (Checked -> action) -> Attribute action
onChecked Checked -> action
f = MisoString
-> Decoder Checked
-> (Checked -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"change" Decoder Checked
checkedDecoder (\Checked
action JSVal
_ -> Checked -> action
f Checked
action)
onClick :: action -> Attribute action
onClick :: forall action. action -> Attribute action
onClick action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"click" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onClickWith :: (JSVal -> action) -> Attribute action
onClickWith :: forall action. (JSVal -> action) -> Attribute action
onClickWith JSVal -> action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"click" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
domRef -> JSVal -> action
action JSVal
domRef
onFocus :: action -> Attribute action
onFocus :: forall action. action -> Attribute action
onFocus action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"focus" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onDoubleClick :: action -> Attribute action
onDoubleClick :: forall action. action -> Attribute action
onDoubleClick action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"dblclick" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onInput :: (MisoString -> action) -> Attribute action
onInput :: forall action. (MisoString -> action) -> Attribute action
onInput MisoString -> action
f = MisoString
-> Decoder MisoString
-> (MisoString -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"input" Decoder MisoString
valueDecoder (\MisoString
action JSVal
_ -> MisoString -> action
f MisoString
action)
onChange :: (MisoString -> action) -> Attribute action
onChange :: forall action. (MisoString -> action) -> Attribute action
onChange MisoString -> action
f = MisoString
-> Decoder MisoString
-> (MisoString -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"change" Decoder MisoString
valueDecoder (\MisoString
action JSVal
_ -> MisoString -> action
f MisoString
action)
onChangeWith :: (MisoString -> JSVal -> action) -> Attribute action
onChangeWith :: forall action. (MisoString -> JSVal -> action) -> Attribute action
onChangeWith = MisoString
-> Decoder MisoString
-> (MisoString -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"change" Decoder MisoString
valueDecoder
onSelect :: (MisoString -> action) -> Attribute action
onSelect :: forall action. (MisoString -> action) -> Attribute action
onSelect MisoString -> action
f = MisoString
-> Decoder MisoString
-> (MisoString -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"select" Decoder MisoString
valueDecoder (\MisoString
action JSVal
_ -> MisoString -> action
f MisoString
action)
onKeyDownWithInfo :: (KeyInfo -> action) -> Attribute action
onKeyDownWithInfo :: forall action. (KeyInfo -> action) -> Attribute action
onKeyDownWithInfo KeyInfo -> action
f = MisoString
-> Decoder KeyInfo
-> (KeyInfo -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"keydown" Decoder KeyInfo
keyInfoDecoder (\KeyInfo
action JSVal
_ -> KeyInfo -> action
f KeyInfo
action)
onKeyDown :: (KeyCode -> action) -> Attribute action
onKeyDown :: forall action. (KeyCode -> action) -> Attribute action
onKeyDown KeyCode -> action
f = MisoString
-> Decoder KeyCode
-> (KeyCode -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"keydown" Decoder KeyCode
keycodeDecoder (\KeyCode
action JSVal
_ -> KeyCode -> action
f KeyCode
action)
onKeyPress :: (KeyCode -> action) -> Attribute action
onKeyPress :: forall action. (KeyCode -> action) -> Attribute action
onKeyPress KeyCode -> action
f = MisoString
-> Decoder KeyCode
-> (KeyCode -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"keypress" Decoder KeyCode
keycodeDecoder (\KeyCode
action JSVal
_ -> KeyCode -> action
f KeyCode
action)
onKeyUp :: (KeyCode -> action) -> Attribute action
onKeyUp :: forall action. (KeyCode -> action) -> Attribute action
onKeyUp KeyCode -> action
f = MisoString
-> Decoder KeyCode
-> (KeyCode -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"keyup" Decoder KeyCode
keycodeDecoder (\KeyCode
action JSVal
_ -> KeyCode -> action
f KeyCode
action)
onMouseUp :: action -> Attribute action
onMouseUp :: forall action. action -> Attribute action
onMouseUp action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"mouseup" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onMouseDown :: action -> Attribute action
onMouseDown :: forall action. action -> Attribute action
onMouseDown action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"mousedown" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onMouseEnter :: action -> Attribute action
onMouseEnter :: forall action. action -> Attribute action
onMouseEnter action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"mouseenter" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onMouseLeave :: action -> Attribute action
onMouseLeave :: forall action. action -> Attribute action
onMouseLeave action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"mouseleave" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onMouseOver :: action -> Attribute action
onMouseOver :: forall action. action -> Attribute action
onMouseOver action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"mouseover" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onMouseOut :: action -> Attribute action
onMouseOut :: forall action. action -> Attribute action
onMouseOut action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"mouseout" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onDragStart :: action -> Attribute action
onDragStart :: forall action. action -> Attribute action
onDragStart action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"dragstart" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onDragOver :: action -> Attribute action
onDragOver :: forall action. action -> Attribute action
onDragOver action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"dragover" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onDragEnd :: action -> Attribute action
onDragEnd :: forall action. action -> Attribute action
onDragEnd action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"dragend" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onDragEnter :: action -> Attribute action
onDragEnter :: forall action. action -> Attribute action
onDragEnter action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"dragenter" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onDragLeave :: action -> Attribute action
onDragLeave :: forall action. action -> Attribute action
onDragLeave action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"dragleave" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onDrag :: action -> Attribute action
onDrag :: forall action. action -> Attribute action
onDrag action
action = MisoString
-> Decoder () -> (() -> JSVal -> action) -> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"drag" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onDrop :: AllowDrop -> action -> Attribute action
onDrop :: forall action. AllowDrop -> action -> Attribute action
onDrop (AllowDrop Capture
allowDrop) action
action =
Options
-> MisoString
-> Decoder ()
-> (() -> JSVal -> action)
-> Attribute action
forall r action.
Options
-> MisoString
-> Decoder r
-> (r -> JSVal -> action)
-> Attribute action
onWithOptions Options
defaultOptions { preventDefault = allowDrop }
MisoString
"drop" Decoder ()
emptyDecoder (\() JSVal
_ -> action
action)
onSubmit :: action -> Attribute action
onSubmit :: forall action. action -> Attribute action
onSubmit action
action =
Options
-> MisoString
-> Decoder ()
-> (() -> JSVal -> action)
-> Attribute action
forall r action.
Options
-> MisoString
-> Decoder r
-> (r -> JSVal -> action)
-> Attribute action
onWithOptions Options
defaultOptions { preventDefault = True }
MisoString
"submit" Decoder ()
emptyDecoder ((() -> JSVal -> action) -> Attribute action)
-> (() -> JSVal -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() JSVal
_ -> action
action
onPointerUp :: (PointerEvent -> action) -> Attribute action
onPointerUp :: forall action. (PointerEvent -> action) -> Attribute action
onPointerUp PointerEvent -> action
f = MisoString
-> Decoder PointerEvent
-> (PointerEvent -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"pointerup" Decoder PointerEvent
pointerDecoder (\PointerEvent
action JSVal
_ -> PointerEvent -> action
f PointerEvent
action)
onPointerDown :: (PointerEvent -> action) -> Attribute action
onPointerDown :: forall action. (PointerEvent -> action) -> Attribute action
onPointerDown PointerEvent -> action
f = MisoString
-> Decoder PointerEvent
-> (PointerEvent -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"pointerdown" Decoder PointerEvent
pointerDecoder (\PointerEvent
action JSVal
_ -> PointerEvent -> action
f PointerEvent
action)
onPointerEnter :: (PointerEvent -> action) -> Attribute action
onPointerEnter :: forall action. (PointerEvent -> action) -> Attribute action
onPointerEnter PointerEvent -> action
f = MisoString
-> Decoder PointerEvent
-> (PointerEvent -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"pointerenter" Decoder PointerEvent
pointerDecoder (\PointerEvent
action JSVal
_ -> PointerEvent -> action
f PointerEvent
action)
onPointerLeave :: (PointerEvent -> action) -> Attribute action
onPointerLeave :: forall action. (PointerEvent -> action) -> Attribute action
onPointerLeave PointerEvent -> action
f = MisoString
-> Decoder PointerEvent
-> (PointerEvent -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"pointerleave" Decoder PointerEvent
pointerDecoder (\PointerEvent
action JSVal
_ -> PointerEvent -> action
f PointerEvent
action)
onPointerOver :: (PointerEvent -> action) -> Attribute action
onPointerOver :: forall action. (PointerEvent -> action) -> Attribute action
onPointerOver PointerEvent -> action
f = MisoString
-> Decoder PointerEvent
-> (PointerEvent -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"pointerover" Decoder PointerEvent
pointerDecoder (\PointerEvent
action JSVal
_ -> PointerEvent -> action
f PointerEvent
action)
onPointerOut :: (PointerEvent -> action) -> Attribute action
onPointerOut :: forall action. (PointerEvent -> action) -> Attribute action
onPointerOut PointerEvent -> action
f = MisoString
-> Decoder PointerEvent
-> (PointerEvent -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"pointerout" Decoder PointerEvent
pointerDecoder (\PointerEvent
action JSVal
_ -> PointerEvent -> action
f PointerEvent
action)
onPointerCancel :: (PointerEvent -> action) -> Attribute action
onPointerCancel :: forall action. (PointerEvent -> action) -> Attribute action
onPointerCancel PointerEvent -> action
f = MisoString
-> Decoder PointerEvent
-> (PointerEvent -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"pointercancel" Decoder PointerEvent
pointerDecoder (\PointerEvent
action JSVal
_ -> PointerEvent -> action
f PointerEvent
action)
onPointerMove :: (PointerEvent -> action) -> Attribute action
onPointerMove :: forall action. (PointerEvent -> action) -> Attribute action
onPointerMove PointerEvent -> action
f = MisoString
-> Decoder PointerEvent
-> (PointerEvent -> JSVal -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> JSVal -> action) -> Attribute action
on MisoString
"pointermove" Decoder PointerEvent
pointerDecoder (\PointerEvent
action JSVal
_ -> PointerEvent -> action
f PointerEvent
action)