Copyright | (C) 2014-15 Joel Burget |
---|---|
License | MIT |
Maintainer | Joel Burget <joelburget@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- data Color = Color Int Int Int
- getAnimationState :: Monad m => ReactT ty m (AnimationState ty)
- class Animatable a where
- data ReactClass ty
- createClass :: (ClassState ty -> React ty ()) -> (ClassState ty -> Signal ty -> (ClassState ty, [AnimConfig ty])) -> ClassState ty -> AnimationState ty -> [Signal ty] -> IO (ReactClass ty)
- locally :: Monad m => Narrowing general local -> ReactT local m x -> ReactT general m x
- data Narrowing general local = Narrowing {
- localizeAnimationState :: AnimationState general -> AnimationState local
- generalizeSignal :: Signal local -> Signal general
- cancelRender :: RenderHandle -> IO ()
- render :: Elem -> ReactClass ty -> IO RenderHandle
- newtype ReactT ty m a = ReactT {
- runReactT :: AnimationState ty -> m ([ReactNode (Signal ty)], a)
- type React ty = ReactT ty Identity
- class ReactKey ty where
- type ClassState ty :: *
- type AnimationState ty :: *
- type Signal ty :: *
- newtype RenderHandle = RenderHandle Int
- 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 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
- data EventProperties e = EventProperties {
- bubbles :: !Bool
- cancelable :: !Bool
- currentTarget :: !e
- defaultPrevented :: !Bool
- eventPhase :: !Int
- isTrusted :: !Bool
- evtTarget :: !e
- eventType :: !JSString
- data ModifierKeys = ModifierKeys {}
- data MouseEvent = MouseEvent {}
- data KeyboardEvent = KeyboardEvent {}
- newtype ChangeEvent = ChangeEvent {
- targetValue :: JSString
- data FocusEvent e = FocusEvent {
- domEventTarget :: !e
- relatedTarget :: !e
Documentation
24-bit colors which can be interpolated.
getAnimationState :: Monad m => ReactT ty m (AnimationState ty) Source
class Animatable a where Source
Properties that can animate.
Numeric values like width
and height
, as well as colors.
Use an easing function to interpolate between two values
Add two animations
Subtract two animations
Animatable Double | |
Animatable () | |
Animatable Color | |
(Animatable a, Animatable b) => Animatable (a, b) | |
(Animatable a, Animatable b, Animatable c) => Animatable (a, b, c) |
data ReactClass ty Source
A ReactClass
is a standalone component of a user interface which
contains the state necessary to render and animate itself. Classes are
a tool for scoping.
Use createClass
to construct.
:: (ClassState ty -> React ty ()) | render function |
-> (ClassState ty -> Signal ty -> (ClassState ty, [AnimConfig ty])) | transition function |
-> ClassState ty | initial state |
-> AnimationState ty | initial animation state |
-> [Signal ty] | |
-> IO (ReactClass ty) |
ReactClass
smart contstructor.
data Narrowing general local Source
Narrowing | |
|
cancelRender :: RenderHandle -> IO () Source
render :: Elem -> ReactClass ty -> IO RenderHandle Source
ReactT | |
|
A ReactKey
is a type, which conventionally has no constructors,
mapping to the type of state, animation state, and signals associated
with a page fragment or class.
Example:
data Slider -- note the key has no constructors data SliderState = Open | Closed data SliderSignal = SlideOpen | SlideClosed instance ReactKey Slider where type ClassState Slider = SliderState type AnimationState Slider = Double type Signal Slider = SliderSignal -- this page fragment has access to the animation stateDouble
and can -- emitSliderSignal
s. pageFragment :: React Slider () pageFragment = div_ ... -- this class stores the class state and animation state. its internals -- can emitSliderSignal
s. sliderClass :: ReactClass Slider () sliderClass = ...
type ClassState ty :: * Source
The state needed to render a class (ignoring animation)
type AnimationState ty :: * Source
The state needed to animate a class
The type of signals a class can send
ReactKey () |
data AnimConfig ty Source
forall a . Animatable a => AnimConfig | |
|
Standard easing functions. These are used to interpolate
smoothly.
See here for visualizations.
data EventProperties e Source
Low level properties common to all events
EventProperties | |
|
NFData e => NFData (EventProperties e) |
data ModifierKeys Source
data FocusEvent e Source
FocusEvent | |
|
NFData e => NFData (FocusEvent e) |