Skip to content

Commit

Permalink
Refactor events (#144)
Browse files Browse the repository at this point in the history
  • Loading branch information
ethul committed Apr 18, 2018
1 parent db05c85 commit bd3933d
Show file tree
Hide file tree
Showing 5 changed files with 261 additions and 29 deletions.
1 change: 1 addition & 0 deletions .gitignore
Expand Up @@ -2,5 +2,6 @@
bower_components/
node_modules/
output/
yarn-error.log
.psc-package
.psc-ide-port
2 changes: 1 addition & 1 deletion src/React.purs
Expand Up @@ -71,7 +71,7 @@ import Control.Monad.Eff.Uncurried (EffFn2, runEffFn2)

import Data.Nullable (Nullable)

import React.SyntheticEvent (preventDefault, isDefaultPrevented, stopPropagation, isPropagationStopped, persist) as SyntheticEvent
import React.SyntheticEvent as SyntheticEvent

import Unsafe.Coerce (unsafeCoerce)

Expand Down
9 changes: 6 additions & 3 deletions src/React/DOM/Props.purs
Expand Up @@ -2,10 +2,13 @@ module React.DOM.Props where

import Data.Nullable (Nullable)

import React (SyntheticEventHandlerContext, Ref, handle)
import React
( Ref
, handle

import React.SyntheticEvent
( SyntheticEvent
, SyntheticEventHandlerContext

, SyntheticEvent
, SyntheticAnimationEvent
, SyntheticClipboardEvent
, SyntheticCompositionEvent
Expand Down
16 changes: 16 additions & 0 deletions src/React/SyntheticEvent.js
Expand Up @@ -29,3 +29,19 @@ exports.persist = function persist(event) {
return event.persist();
};
};

exports.getModifierState = function getModifierState(key) {
return function(event) {
return function() {
return event.getModifierState(key);
};
};
};

exports.unsafeGet = function unsafeGet(key) {
return function (event) {
return function () {
return event[key];
};
};
};
262 changes: 237 additions & 25 deletions src/React/SyntheticEvent.purs
Expand Up @@ -22,54 +22,118 @@ module React.SyntheticEvent
, SyntheticAnimationEvent'
, SyntheticClipboardEvent'
, SyntheticCompositionEvent'
, SyntheticKeyboardEvent'
, SyntheticFocusEvent'
, SyntheticKeyboardEvent'
, SyntheticMouseEvent'
, SyntheticTouchEvent'
, SyntheticTransitionEvent'
, SyntheticUIEvent'
, SyntheticWheelEvent'

, SyntheticEvent_

, NativeEventTarget
, NativeEvent
, NativeDataTransfer
, NativeAbstractView
, NativeTouchList

, bubbles
, cancelable
, currentTarget
, defaultPrevented
, eventPhase
, isTrusted
, nativeEvent
, preventDefault
, isDefaultPrevented
, stopPropagation
, isPropagationStopped
, target
, timeStamp
, type_
, persist
, animationName
, clipboardData
, data_
, relatedTarget
, charCode
, key
, keyCode
, locale
, location
, repeat
, which
, button
, buttons
, clientX
, clientY
, pageX
, pageY
, screenX
, screenY
, changedTouches
, targetTouches
, touches
, altKey
, ctrlKey
, getModifierState
, metaKey
, shiftKey
, propertyName
, pseudoElement
, elapsedTime
, detail
, view
, deltaMode
, deltaX
, deltaY
, deltaZ
) where

import Prelude

import Control.Monad.Eff (Eff)

type SyntheticEvent = Record (SyntheticEvent' ())
import Data.Symbol (class IsSymbol, SProxy(..), reflectSymbol)

type SyntheticEvent
= SyntheticEvent_ (SyntheticEvent' ())

type SyntheticAnimationEvent
= SyntheticEvent_ (SyntheticAnimationEvent' (SyntheticEvent' ()))

type SyntheticAnimationEvent = Record (SyntheticAnimationEvent' (SyntheticEvent' ()))
type SyntheticClipboardEvent
= SyntheticEvent_ (SyntheticClipboardEvent' (SyntheticEvent' ()))

type SyntheticClipboardEvent = Record (SyntheticClipboardEvent' (SyntheticEvent' ()))
type SyntheticCompositionEvent
= SyntheticEvent_ (SyntheticCompositionEvent' (SyntheticUIEvent' (SyntheticEvent' ())))

type SyntheticCompositionEvent = Record (SyntheticCompositionEvent' (SyntheticUIEvent' (SyntheticEvent' ())))
type SyntheticInputEvent
= SyntheticEvent_ (SyntheticUIEvent' (SyntheticEvent' ()))

type SyntheticInputEvent = Record (SyntheticUIEvent' (SyntheticEvent' ()))
type SyntheticKeyboardEvent
= SyntheticEvent_ (SyntheticKeyboardEvent' (SyntheticUIEvent' (SyntheticEvent' ())))

type SyntheticKeyboardEvent = Record (SyntheticKeyboardEvent' (SyntheticUIEvent' (SyntheticEvent' ())))
type SyntheticFocusEvent
= SyntheticEvent_ (SyntheticFocusEvent' (SyntheticUIEvent' (SyntheticEvent' ())))

type SyntheticFocusEvent = Record (SyntheticFocusEvent' (SyntheticUIEvent' (SyntheticEvent' ())))
type SyntheticMouseEvent
= SyntheticEvent_ (SyntheticMouseEvent' (SyntheticUIEvent' (SyntheticEvent' ())))

type SyntheticMouseEvent = Record (SyntheticMouseEvent' (SyntheticUIEvent' (SyntheticEvent' ())))
type SyntheticTouchEvent
= SyntheticEvent_ (SyntheticTouchEvent' (SyntheticUIEvent' (SyntheticEvent' ())))

type SyntheticTouchEvent = Record (SyntheticTouchEvent' (SyntheticUIEvent' (SyntheticEvent' ())))
type SyntheticTransitionEvent
= SyntheticEvent_ (SyntheticTransitionEvent' (SyntheticEvent' ()))

type SyntheticTransitionEvent = Record (SyntheticTransitionEvent' (SyntheticEvent' ()))
type SyntheticUIEvent
= SyntheticEvent_ (SyntheticUIEvent' (SyntheticEvent' ()))

type SyntheticUIEvent = Record (SyntheticUIEvent' (SyntheticEvent' ()))
type SyntheticWheelEvent
= SyntheticEvent_ (SyntheticWheelEvent' (SyntheticMouseEvent' (SyntheticEvent' ())))

type SyntheticWheelEvent = Record (SyntheticWheelEvent' (SyntheticMouseEvent' (SyntheticEvent' ())))
foreign import data SyntheticEvent_ :: # Type -> Type

foreign import data NativeEventTarget :: Type

Expand All @@ -81,16 +145,6 @@ foreign import data NativeAbstractView :: Type

foreign import data NativeTouchList :: Type

foreign import preventDefault :: forall eff r. Record (SyntheticEvent' r) -> Eff eff Unit

foreign import isDefaultPrevented :: forall eff r. Record (SyntheticEvent' r) -> Eff eff Boolean

foreign import stopPropagation :: forall eff r. Record (SyntheticEvent' r) -> Eff eff Unit

foreign import isPropagationStopped :: forall eff r. Record (SyntheticEvent' r) -> Eff eff Boolean

foreign import persist :: forall eff r. Record (SyntheticEvent' r) -> Eff eff Unit

type SyntheticEvent' r
= ( bubbles :: Boolean
, cancelable :: Boolean
Expand Down Expand Up @@ -129,9 +183,9 @@ type SyntheticFocusEvent' r

type SyntheticKeyboardEvent' r
= ( altKey :: Boolean
, charCode :: Int
, ctrlKey :: Boolean
, getModifierState :: String -> Boolean
, charCode :: Int
, key :: String
, keyCode :: Number
, locale :: String
Expand Down Expand Up @@ -167,8 +221,8 @@ type SyntheticTouchEvent' r
, ctrlKey :: Boolean
, getModifierState :: String -> Boolean
, metaKey :: Boolean
, shiftKey :: Boolean
, targetTouches :: NativeTouchList
, shiftKey :: Boolean
, touches :: NativeTouchList
| r
)
Expand All @@ -193,3 +247,161 @@ type SyntheticWheelEvent' r
, deltaZ :: Number
| r
)

bubbles :: forall eff r. SyntheticEvent_ (bubbles :: Boolean | r) -> Eff eff Boolean
bubbles = get (SProxy :: SProxy "bubbles")

cancelable :: forall eff r. SyntheticEvent_ (cancelable :: Boolean | r) -> Eff eff Boolean
cancelable = get (SProxy :: SProxy "cancelable")

currentTarget :: forall eff r. SyntheticEvent_ (currentTarget :: NativeEventTarget | r) -> Eff eff NativeEventTarget
currentTarget = get (SProxy :: SProxy "currentTarget")

defaultPrevented :: forall eff r. SyntheticEvent_ (defaultPrevented :: Boolean | r) -> Eff eff Boolean
defaultPrevented = get (SProxy :: SProxy "defaultPrevented")

eventPhase :: forall eff r. SyntheticEvent_ (eventPhase :: Number | r) -> Eff eff Number
eventPhase = get (SProxy :: SProxy "eventPhase")

isTrusted :: forall eff r. SyntheticEvent_ (isTrusted :: Boolean | r) -> Eff eff Boolean
isTrusted = get (SProxy :: SProxy "isTrusted")

nativeEvent :: forall eff r. SyntheticEvent_ (nativeEvent :: NativeEvent | r) -> Eff eff NativeEvent
nativeEvent = get (SProxy :: SProxy "nativeEvent")

target :: forall eff r. SyntheticEvent_ (target :: NativeEventTarget | r) -> Eff eff NativeEventTarget
target = get (SProxy :: SProxy "target")

timeStamp :: forall eff r. SyntheticEvent_ (timeStamp :: Number | r) -> Eff eff Number
timeStamp = get (SProxy :: SProxy "timeStamp")

type_ :: forall eff r. SyntheticEvent_ (type :: String | r) -> Eff eff String
type_ = get (SProxy :: SProxy "type")

animationName :: forall eff r. SyntheticEvent_ (animationName :: String | r) -> Eff eff String
animationName = get (SProxy :: SProxy "animationName")

clipboardData :: forall eff r. SyntheticEvent_ (clipboardData :: NativeDataTransfer | r) -> Eff eff NativeDataTransfer
clipboardData = get (SProxy :: SProxy "clipboardData")

data_ :: forall eff r. SyntheticEvent_ (data :: String | r) -> Eff eff String
data_ = get (SProxy :: SProxy "data")

relatedTarget :: forall eff r. SyntheticEvent_ (relatedTarget :: NativeEventTarget | r) -> Eff eff NativeEventTarget
relatedTarget = get (SProxy :: SProxy "relatedTarget")

charCode :: forall eff r. SyntheticEvent_ (charCode :: Int | r) -> Eff eff Int
charCode = get (SProxy :: SProxy "charCode")

key :: forall eff r. SyntheticEvent_ (key :: String | r) -> Eff eff String
key = get (SProxy :: SProxy "key")

keyCode :: forall eff r. SyntheticEvent_ (keyCode :: Number | r) -> Eff eff Number
keyCode = get (SProxy :: SProxy "keyCode")

locale :: forall eff r. SyntheticEvent_ (locale :: String | r) -> Eff eff String
locale = get (SProxy :: SProxy "locale")

location :: forall eff r. SyntheticEvent_ (location :: Number | r) -> Eff eff Number
location = get (SProxy :: SProxy "location")

repeat :: forall eff r. SyntheticEvent_ (repeat :: Boolean | r) -> Eff eff Boolean
repeat = get (SProxy :: SProxy "repeat")

which :: forall eff r. SyntheticEvent_ (which :: Number | r) -> Eff eff Number
which = get (SProxy :: SProxy "which")

button :: forall eff r. SyntheticEvent_ (button :: Number | r) -> Eff eff Number
button = get (SProxy :: SProxy "button")

buttons :: forall eff r. SyntheticEvent_ (buttons :: Number | r) -> Eff eff Number
buttons = get (SProxy :: SProxy "buttons")

clientX :: forall eff r. SyntheticEvent_ (clientX :: Number | r) -> Eff eff Number
clientX = get (SProxy :: SProxy "clientX")

clientY :: forall eff r. SyntheticEvent_ (clientY :: Number | r) -> Eff eff Number
clientY = get (SProxy :: SProxy "clientY")

pageX :: forall eff r. SyntheticEvent_ (pageX :: Number | r) -> Eff eff Number
pageX = get (SProxy :: SProxy "pageX")

pageY :: forall eff r. SyntheticEvent_ (pageY :: Number | r) -> Eff eff Number
pageY = get (SProxy :: SProxy "pageY")

screenX :: forall eff r. SyntheticEvent_ (screenX :: Number | r) -> Eff eff Number
screenX = get (SProxy :: SProxy "screenX")

screenY :: forall eff r. SyntheticEvent_ (screenY :: Number | r) -> Eff eff Number
screenY = get (SProxy :: SProxy "screenY")

changedTouches :: forall eff r. SyntheticEvent_ (changedTouches :: NativeTouchList | r) -> Eff eff NativeTouchList
changedTouches = get (SProxy :: SProxy "changedTouches")

targetTouches :: forall eff r. SyntheticEvent_ (targetTouches :: NativeTouchList | r) -> Eff eff NativeTouchList
targetTouches = get (SProxy :: SProxy "targetTouches")

touches :: forall eff r. SyntheticEvent_ (touches :: NativeTouchList | r) -> Eff eff NativeTouchList
touches = get (SProxy :: SProxy "touches")

altKey :: forall eff r. SyntheticEvent_ (altKey :: Boolean | r) -> Eff eff Boolean
altKey = get (SProxy :: SProxy "altKey")

ctrlKey :: forall eff r. SyntheticEvent_ (ctrlKey :: Boolean | r) -> Eff eff Boolean
ctrlKey = get (SProxy :: SProxy "ctrlKey")

metaKey :: forall eff r. SyntheticEvent_ (metaKey :: Boolean | r) -> Eff eff Boolean
metaKey = get (SProxy :: SProxy "metaKey")

shiftKey :: forall eff r. SyntheticEvent_ (shiftKey :: Boolean | r) -> Eff eff Boolean
shiftKey = get (SProxy :: SProxy "shiftKey")

propertyName :: forall eff r. SyntheticEvent_ (propertyName :: String | r) -> Eff eff String
propertyName = get (SProxy :: SProxy "propertyName")

pseudoElement :: forall eff r. SyntheticEvent_ (pseudoElement :: String | r) -> Eff eff String
pseudoElement = get (SProxy :: SProxy "pseudoElement")

elapsedTime :: forall eff r. SyntheticEvent_ (elapsedTime :: Number | r) -> Eff eff Number
elapsedTime = get (SProxy :: SProxy "elapsedTime")

detail :: forall eff r. SyntheticEvent_ (detail :: Number | r) -> Eff eff Number
detail = get (SProxy :: SProxy "detail")

view :: forall eff r. SyntheticEvent_ (view :: NativeAbstractView | r) -> Eff eff NativeAbstractView
view = get (SProxy :: SProxy "view")

deltaMode :: forall eff r. SyntheticEvent_ (deltaMode :: Number | r) -> Eff eff Number
deltaMode = get (SProxy :: SProxy "deltaMode")

deltaX :: forall eff r. SyntheticEvent_ (deltaX :: Number | r) -> Eff eff Number
deltaX = get (SProxy :: SProxy "deltaX")

deltaY :: forall eff r. SyntheticEvent_ (deltaY :: Number | r) -> Eff eff Number
deltaY = get (SProxy :: SProxy "deltaY")

deltaZ :: forall eff r. SyntheticEvent_ (deltaZ :: Number | r) -> Eff eff Number
deltaZ = get (SProxy :: SProxy "deltaZ")

foreign import preventDefault :: forall eff r. SyntheticEvent_ r -> Eff eff Unit

foreign import isDefaultPrevented :: forall eff r. SyntheticEvent_ r -> Eff eff Boolean

foreign import stopPropagation :: forall eff r. SyntheticEvent_ r -> Eff eff Unit

foreign import isPropagationStopped :: forall eff r. SyntheticEvent_ r -> Eff eff Boolean

foreign import persist :: forall eff r. SyntheticEvent_ r -> Eff eff Unit

foreign import getModifierState :: forall eff r. String -> SyntheticEvent_ (getModifierState :: String -> Boolean | r) -> Eff eff Boolean

get
:: forall eff l r s a
. RowCons l a r s
=> IsSymbol l
=> SProxy l
-> SyntheticEvent_ s
-> Eff eff a
get l r = unsafeGet (reflectSymbol l) r

foreign import unsafeGet :: forall eff r a. String -> SyntheticEvent_ r -> Eff eff a

0 comments on commit bd3933d

Please sign in to comment.