module Graphics.UI.Threepenny.Events (
    -- * Synopsis
    -- | Events on DOM elements.

    -- * Convenience events
    valueChange, selectionChange, checkedChange,

    -- * Standard DOM events
    click, contextmenu, mousemove, mousedown, mouseup,
    hover, leave,
    focus, blur,
    KeyCode, keyup, keydown, keypress,

    -- * Migration
    roundCoordinates
    ) where

import Graphics.UI.Threepenny.Attributes
import Graphics.UI.Threepenny.Core

silence :: Event a -> Event ()
silence = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> b -> a
const ())

{-----------------------------------------------------------------------------
    Events
------------------------------------------------------------------------------}
-- | Event that occurs when the /user/ changes the value of the input element.
valueChange :: Element -> Event String
valueChange :: Element -> Event String
valueChange Element
el = forall {t} {b}. Element -> (t -> UI b) -> Event t -> Event b
unsafeMapUI Element
el (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall x i o. ReadWriteAttr x i o -> x -> UI o
get Attr Element String
value Element
el) (String -> Element -> Event EventData
domEvent String
"keydown" Element
el)

unsafeMapUI :: Element -> (t -> UI b) -> Event t -> Event b
unsafeMapUI Element
el t -> UI b
f = forall a b. (a -> IO b) -> Event a -> Event b
unsafeMapIO (\t
a -> Element -> IO Window
getWindow Element
el forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> forall a. Window -> UI a -> IO a
runUI Window
w (t -> UI b
f t
a))

-- | Event that occurs when the /user/ changes the selection of a @<select>@ element.
selectionChange :: Element -> Event (Maybe Int)
selectionChange :: Element -> Event (Maybe Int)
selectionChange Element
el = forall {t} {b}. Element -> (t -> UI b) -> Event t -> Event b
unsafeMapUI Element
el (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall x i o. ReadWriteAttr x i o -> x -> UI o
get Attr Element (Maybe Int)
selection Element
el) (Element -> Event ()
click Element
el)

-- | Event that occurs when the /user/ changes the checked status of an input
-- element of type checkbox.
checkedChange :: Element -> Event Bool
checkedChange :: Element -> Event Bool
checkedChange Element
el = forall {t} {b}. Element -> (t -> UI b) -> Event t -> Event b
unsafeMapUI Element
el (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall x i o. ReadWriteAttr x i o -> x -> UI o
get Attr Element Bool
checked Element
el) (Element -> Event ()
click Element
el)

{-----------------------------------------------------------------------------
    DOM Events
------------------------------------------------------------------------------}
-- | Mouse click.
click :: Element -> Event ()
click :: Element -> Event ()
click = forall {a}. Event a -> Event ()
silence forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"click"

-- | Context menu event.
--
-- The mouse coordinates are relative to the upper left corner of the element.
contextmenu :: Element -> Event (Double,Double)
contextmenu :: Element -> Event (Double, Double)
contextmenu = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap EventData -> (Double, Double)
readCoordinates forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"contextmenu"

-- | Mouse enters an element.
hover :: Element -> Event ()
hover :: Element -> Event ()
hover = forall {a}. Event a -> Event ()
silence forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"mouseenter"

-- | Event that periodically occurs while the mouse is moving over an element.
--
-- The event value represents the mouse coordinates
-- relative to the upper left corner of the element.
--
-- Note: The @<body>@ element responds to mouse move events,
-- but only in the area occupied by actual content,
-- not the whole browser window.
mousemove :: Element -> Event (Double,Double)
mousemove :: Element -> Event (Double, Double)
mousemove = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap EventData -> (Double, Double)
readCoordinates forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"mousemove"

-- NB:
-- The return types of mouse events have been redefined from @long@
-- to @double@ in the CSS Object Model View Model working draft,
-- which browsers have begun to adopt.
-- See https://developer.mozilla.org/en-US/docs/Web/API/MouseEvent#Specifications
-- and https://developer.mozilla.org/en-US/docs/Web/API/MouseEvent/pageX
--
-- Similarly, we rely on jQuery's @.offset()@ to return
-- coordinates relative to the upper left corner of the
-- element, and this may return fractional data.
-- https://api.jquery.com/offset/
readCoordinates :: EventData -> (Double,Double)
readCoordinates :: EventData -> (Double, Double)
readCoordinates EventData
json = (Double
x,Double
y)
    where [Double
x,Double
y] = forall a. FromJSON a => EventData -> a
unsafeFromJSON EventData
json

-- | Round a pair of `Double` to the next integers.
-- This function helps you migrate from previous versions of Threepenny-GUI.
--
-- The return types of mouse events (`mousedown`, `mouseup`, `mousemove`, `contextmenu`) 
-- have been redefined from @long@
-- to @double@ in the CSS Object Model View Model working draft,
-- which browsers have begun to adopt.
--
-- See https://developer.mozilla.org/en-US/docs/Web/API/MouseEvent#Specifications
--
-- and https://developer.mozilla.org/en-US/docs/Web/API/MouseEvent/pageX
roundCoordinates :: (Double,Double) -> (Int,Int)
roundCoordinates :: (Double, Double) -> (Int, Int)
roundCoordinates (Double
x,Double
y) = (forall a b. (RealFrac a, Integral b) => a -> b
round Double
x, forall a b. (RealFrac a, Integral b) => a -> b
round Double
y)

-- | Mouse down event.
--
-- The mouse coordinates are relative to the upper left corner of the element.
mousedown :: Element -> Event (Double,Double)
mousedown :: Element -> Event (Double, Double)
mousedown = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap EventData -> (Double, Double)
readCoordinates forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"mousedown"

-- | Mouse up event.
--
-- The mouse coordinates are relative to the upper left corner of the element.
mouseup :: Element -> Event (Double,Double)
mouseup :: Element -> Event (Double, Double)
mouseup = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap EventData -> (Double, Double)
readCoordinates forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"mouseup"

-- | Mouse leaving an element.
leave :: Element -> Event ()
leave :: Element -> Event ()
leave = forall {a}. Event a -> Event ()
silence forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"mouseleave"

-- | Element receives focus.
focus :: Element -> Event ()
focus :: Element -> Event ()
focus = forall {a}. Event a -> Event ()
silence forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"focus"

-- | Element loses focus.
blur :: Element -> Event ()
blur :: Element -> Event ()
blur = forall {a}. Event a -> Event ()
silence forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"blur"


type KeyCode = Int

-- | Key pressed while element has focus.
-- Returns the keycode (as opposed to the ASCII value) of any key, including
-- SHIFT, CTRL and arrow keys.
keydown :: Element -> Event KeyCode
keydown :: Element -> Event Int
keydown = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. FromJSON a => EventData -> a
unsafeFromJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"keydown"

-- | Key released while element has focus.
keyup :: Element -> Event KeyCode
keyup :: Element -> Event Int
keyup   = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. FromJSON a => EventData -> a
unsafeFromJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"keyup"

-- | Key pressed while element has focus.
-- Returns the actual character, taking into account SHIFT or CAPS LOCK.
keypress :: Element -> Event Char
keypress :: Element -> Event Char
keypress = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Read a => String -> a
read forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromJSON a => EventData -> a
unsafeFromJSON) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Element -> Event EventData
domEvent String
"keypress"