module React.Types where
import Control.Applicative
import Control.DeepSeq
import Control.Monad
import Data.Functor.Identity
import Data.Monoid
import Data.String
import Data.Void
import Haste
import Haste.Foreign
import Haste.JSON
import Haste.Prim
import Lens.Family2
newtype ForeignNode = ForeignNode JSAny deriving (Pack, Unpack)
newtype RawAttrs = RawAttrs JSAny deriving (Pack, Unpack)
newtype ReactArray = ReactArray JSAny deriving (Pack, Unpack)
newtype ForeignClass = ForeignClass JSAny deriving (Pack, Unpack)
newtype RenderHandle = RenderHandle Int
deriving (Pack, Unpack)
data EvtType
= ChangeEvt
| KeyDownEvt
| KeyPressEvt
| KeyUpEvt
| ClickEvt
| DoubleClickEvt
| MouseEnterEvt
| MouseLeaveEvt
data EventHandler signal = EventHandler
{ handler :: RawEvent -> Maybe signal
, evtType :: EvtType
}
newtype RawEvent = RawEvent JSAny deriving (Pack, Unpack)
type Attrs = [(JSString, JSON)]
data ReactNode signal
= Parent JSString Attrs [EventHandler signal] [ReactNode signal]
| Leaf JSString Attrs [EventHandler signal]
| Text String
data Easing
= Linear
| EaseInQuad
| EaseOutQuad
| EaseInOutQuad
| EaseInCubic
| EaseOutCubic
| EaseInOutCubic
| EaseInQuart
| EaseOutQuart
| EaseInOutQuart
| EaseInQuint
| EaseOutQuint
| EaseInOutQuint
| EaseInElastic
| EaseOutElastic
| EaseInOutElastic
| EaseInBounce
| EaseOutBounce
| EaseInOutBounce
| EaseBezier Double Double Double Double
| EaseInSine
| EaseOutSine
deriving (Show, Eq, Ord)
class Animatable a where
interpolate :: Easing
-> a
-> a
-> Double
-> a
animAdd :: a -> a -> a
animSub :: a -> a -> a
animZero :: a
class ReactKey ty where
type ClassState ty :: *
type AnimationState ty :: *
type Signal ty :: *
instance ReactKey () where
type ClassState () = ()
type AnimationState () = ()
type Signal () = Void
data AnimConfig ty = forall a. (Animatable a) => AnimConfig {
duration :: Double
, endpoints :: (a, a)
, lens :: Traversal' (AnimationState ty) a
, easing :: Easing
, onComplete :: Bool -> Maybe (Signal ty)
}
data RunningAnim ty = RunningAnim
{ config :: AnimConfig ty
, beganAt :: Double
}
newtype ReactT ty m a = ReactT
{ runReactT :: AnimationState ty -> m ([ReactNode (Signal ty)], a) }
type React ty = ReactT ty Identity
instance (Monad m, Monoid a) => Monoid (ReactT ty m a) where
mempty = ReactT $ \_ -> return ([], mempty)
mappend f1 f2 = ReactT $ \anim -> do
~(c1, a) <- runReactT f1 anim
~(c2, b) <- runReactT f2 anim
return (c1 <> c2, a <> b)
instance Monad m => Functor (ReactT ty m) where
fmap = liftM
instance Monad m => Applicative (ReactT ty m) where
pure = return
(<*>) = ap
instance (Monad m, a ~ ()) => IsString (ReactT ty m a) where
fromString str = ReactT $ \_ -> return ([Text str], ())
instance Monad m => Monad (ReactT ty m) where
return a = ReactT $ \_ -> return ([], a)
m >>= f = ReactT $ \anim -> do
~(c1, a) <- runReactT m anim
~(c2, b) <- runReactT (f a) anim
return (c1 <> c2, b)
data AttrOrHandler signal
= StaticAttr JSString JSON
| Handler (EventHandler signal)
mkStaticAttr :: JSString -> (a -> JSON) -> a -> AttrOrHandler signal
mkStaticAttr name f a = StaticAttr name (f a)
mkEventHandler :: (NFData signal)
=> (RawEvent -> signal)
-> EvtType
-> (signal -> Maybe signal')
-> AttrOrHandler signal'
mkEventHandler unNative ty handle =
let handle' raw = handle $!! unNative raw
in Handler (EventHandler handle' ty)
separateAttrs :: [AttrOrHandler signal] -> ([EventHandler signal], Attrs)
separateAttrs [] = ([], [])
separateAttrs ((StaticAttr k v):xs) =
let (hs, as) = separateAttrs xs in (hs, (k, v):as)
separateAttrs ((Handler h):xs) =
let (hs, as) = separateAttrs xs in (h:hs, as)
class TermParent result where
type TermParentArg result :: *
termParent :: JSString -> TermParentArg result -> result
instance (Monad m, f ~ ReactT ty m a) => TermParent (f -> ReactT ty m a) where
type TermParentArg (f -> ReactT ty m a) = [AttrOrHandler (Signal ty)]
termParent name attrs children = ReactT $ \anim -> do
~(childNodes, a) <- runReactT children anim
let (hs, as) = separateAttrs attrs
return ([Parent name as hs childNodes], a)
instance Monad m => TermParent (ReactT ty m a) where
type TermParentArg (ReactT ty m a) = ReactT ty m a
termParent name children = ReactT $ \anim -> do
~(childNodes, a) <- runReactT children anim
return ([Parent name [] [] childNodes], a)
termLeaf :: (Monad m, sig ~ Signal ty)
=> JSString
-> [AttrOrHandler sig]
-> ReactT ty m ()
termLeaf name attrs = ReactT $ \_ -> do
let (hs, as) = separateAttrs attrs
return ([Leaf name as hs], ())
data EventProperties e =
EventProperties { bubbles :: !Bool
, cancelable :: !Bool
, currentTarget :: !e
, defaultPrevented :: !Bool
, eventPhase :: !Int
, isTrusted :: !Bool
, evtTarget :: !e
, eventType :: !JSString
}
instance NFData e => NFData (EventProperties e) where
rnf (EventProperties a b c d e f g h) =
a `seq` b `seq` c `seq` d `seq` e `seq` f `seq` g `seq` h `seq` ()
data ModifierKeys =
ModifierKeys { altKey :: !Bool
, ctrlKey :: !Bool
, metaKey :: !Bool
, shiftKey :: !Bool
} deriving (Eq, Show)
instance NFData ModifierKeys where
rnf (ModifierKeys a b c d) = a `seq` b `seq` c `seq` d `seq` ()
data MouseEvent =
MouseEvent {
mouseModifierKeys :: !ModifierKeys
, buttonNum :: !Int
, clientX :: !Double
, clientY :: !Double
, pageX :: !Double
, pageY :: !Double
, screenX :: !Double
, screenY :: !Double
} deriving Show
instance NFData MouseEvent where
rnf (MouseEvent a b c d e f g h) =
a `seq` b `seq` c `seq` d `seq` e `seq` f `seq` g `seq` h `seq` ()
data KeyboardEvent =
KeyboardEvent {
keyboardModifierKeys :: !ModifierKeys
, charCode :: !Int
, key :: !JSString
, keyCode :: !Int
, locale :: !JSString
, location :: !Int
, repeat :: !Bool
, which :: !Int
} deriving Show
instance NFData KeyboardEvent where
rnf (KeyboardEvent a b c d e f g h) =
a `seq` b `seq` c `seq` d `seq` e `seq` f `seq` g `seq` h `seq` ()
newtype ChangeEvent = ChangeEvent { targetValue :: JSString } deriving Show
instance NFData ChangeEvent where
rnf e@(ChangeEvent str) = str `seq` ()
data FocusEvent e =
FocusEvent {
domEventTarget :: !e
, relatedTarget :: !e
}
instance NFData e => NFData (FocusEvent e) where
rnf (FocusEvent a b) = a `seq` b `seq` ()