{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
module Miso.Html.Event
(
on
, onWithOptions
, Options (..)
, defaultOptions
, onClick
, onDoubleClick
, onMouseDown
, onMouseUp
, onMouseEnter
, onMouseLeave
, onMouseOver
, onMouseOut
, onKeyDown
, onKeyPress
, onKeyUp
, onInput
, onChange
, onChecked
, onSubmit
, onBlur
, onFocus
, onDrag
, onDragLeave
, onDragEnter
, onDragEnd
, onDragStart
, onDragOver
, onDrop
) where
import Miso.Html.Internal ( Attribute, on, onWithOptions )
import Miso.Event
import Miso.String (MisoString)
onBlur :: action -> Attribute action
onBlur action = on "blur" emptyDecoder $ \() -> action
onChecked :: (Checked -> action) -> Attribute action
onChecked = on "change" checkedDecoder
onClick :: action -> Attribute action
onClick action = on "click" emptyDecoder $ \() -> action
onFocus :: action -> Attribute action
onFocus action = on "focus" emptyDecoder $ \() -> action
onDoubleClick :: action -> Attribute action
onDoubleClick action = on "dblclick" emptyDecoder $ \() -> action
onInput :: (MisoString -> action) -> Attribute action
onInput = on "input" valueDecoder
onChange :: (MisoString -> action) -> Attribute action
onChange = on "change" valueDecoder
onKeyDown :: (KeyCode -> action) -> Attribute action
onKeyDown = on "keydown" keycodeDecoder
onKeyPress :: (KeyCode -> action) -> Attribute action
onKeyPress = on "keypress" keycodeDecoder
onKeyUp :: (KeyCode -> action) -> Attribute action
onKeyUp = on "keyup" keycodeDecoder
onMouseUp :: action -> Attribute action
onMouseUp action = on "mouseup" emptyDecoder $ \() -> action
onMouseDown :: action -> Attribute action
onMouseDown action = on "mousedown" emptyDecoder $ \() -> action
onMouseEnter :: action -> Attribute action
onMouseEnter action = on "mouseenter" emptyDecoder $ \() -> action
onMouseLeave :: action -> Attribute action
onMouseLeave action = on "mouseleave" emptyDecoder $ \() -> action
onMouseOver :: action -> Attribute action
onMouseOver action = on "mouseover" emptyDecoder $ \() -> action
onMouseOut :: action -> Attribute action
onMouseOut action = on "mouseout" emptyDecoder $ \() -> action
onDragStart :: action -> Attribute action
onDragStart action = on "dragstart" emptyDecoder $ \() -> action
onDragOver :: action -> Attribute action
onDragOver action = on "dragover" emptyDecoder $ \() -> action
onDragEnd :: action -> Attribute action
onDragEnd action = on "dragend" emptyDecoder $ \() -> action
onDragEnter :: action -> Attribute action
onDragEnter action = on "dragenter" emptyDecoder $ \() -> action
onDragLeave :: action -> Attribute action
onDragLeave action = on "dragleave" emptyDecoder $ \() -> action
onDrag :: action -> Attribute action
onDrag action = on "drag" emptyDecoder $ \() -> action
onDrop :: AllowDrop -> action -> Attribute action
onDrop (AllowDrop allowDrop) action =
onWithOptions defaultOptions { preventDefault = allowDrop }
"drop" emptyDecoder (\() -> action)
onSubmit :: action -> Attribute action
onSubmit action =
onWithOptions defaultOptions { preventDefault = True }
"submit" emptyDecoder $ \() -> action