{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Miso.Svg.Event
(
onBegin
, onEnd
, onRepeat
, onAbort
, onError
, onResize
, onScroll
, onLoad
, onUnload
, onZoom
, onActivate
, onClick
, onFocusIn
, onFocusOut
, onMouseDown
, onMouseMove
, onMouseOut
, onMouseOver
, onMouseUp
) where
import Miso.Event (emptyDecoder)
import Miso.Html.Event (on, onClick)
import Miso.Html.Types (Attribute)
onBegin :: action -> Attribute action
onBegin :: forall action. action -> Attribute action
onBegin action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"begin" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onEnd :: action -> Attribute action
onEnd :: forall action. action -> Attribute action
onEnd action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"end" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onRepeat :: action -> Attribute action
onRepeat :: forall action. action -> Attribute action
onRepeat action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"repeat" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onAbort :: action -> Attribute action
onAbort :: forall action. action -> Attribute action
onAbort action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"abort" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onError :: action -> Attribute action
onError :: forall action. action -> Attribute action
onError action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"error" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onResize :: action -> Attribute action
onResize :: forall action. action -> Attribute action
onResize action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"resize" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onScroll :: action -> Attribute action
onScroll :: forall action. action -> Attribute action
onScroll action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"scroll" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onLoad :: action -> Attribute action
onLoad :: forall action. action -> Attribute action
onLoad action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"load" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onUnload :: action -> Attribute action
onUnload :: forall action. action -> Attribute action
onUnload action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"unload" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onZoom :: action -> Attribute action
onZoom :: forall action. action -> Attribute action
onZoom action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"zoom" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onActivate :: action -> Attribute action
onActivate :: forall action. action -> Attribute action
onActivate action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"activate" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onFocusIn :: action -> Attribute action
onFocusIn :: forall action. action -> Attribute action
onFocusIn action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"focusin" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onFocusOut :: action -> Attribute action
onFocusOut :: forall action. action -> Attribute action
onFocusOut action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"focusout" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onMouseDown :: action -> Attribute action
onMouseDown :: forall action. action -> Attribute action
onMouseDown action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"mousedown" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onMouseMove :: action -> Attribute action
onMouseMove :: forall action. action -> Attribute action
onMouseMove action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"mousemove" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onMouseOut :: action -> Attribute action
onMouseOut :: forall action. action -> Attribute action
onMouseOut action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"mouseout" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onMouseOver :: action -> Attribute action
onMouseOver :: forall action. action -> Attribute action
onMouseOver action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"mouseover" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action
onMouseUp :: action -> Attribute action
onMouseUp :: forall action. action -> Attribute action
onMouseUp action
action = MisoString -> Decoder () -> (() -> action) -> Attribute action
forall r action.
MisoString -> Decoder r -> (r -> action) -> Attribute action
on MisoString
"mouseup" Decoder ()
emptyDecoder ((() -> action) -> Attribute action)
-> (() -> action) -> Attribute action
forall a b. (a -> b) -> a -> b
$ \() -> action
action