react-haskell-1.3.0.0: Haskell React bindings

Copyright(C) 2014-15 Joel Burget
LicenseMIT
MaintainerJoel Burget <joelburget@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

React

Description

 

Synopsis

Documentation

data Color Source

24-bit colors which can be interpolated.

Constructors

Color Int Int Int 

class Animatable a where Source

Properties that can animate.

Numeric values like width and height, as well as colors.

Methods

interpolate Source

Arguments

:: Easing

easing function

-> a

from

-> a

to

-> Double
0..1
ratio of time elapsed
-> a 

Use an easing function to interpolate between two values

animAdd :: a -> a -> a Source

Add two animations

animSub :: a -> a -> a Source

Subtract two animations

animZero :: a Source

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.

createClass Source

Arguments

:: (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.

locally :: Monad m => Narrowing general local -> ReactT local m x -> ReactT general m x Source

data Narrowing general local Source

Constructors

Narrowing 

Fields

localizeAnimationState :: AnimationState general -> AnimationState local
 
generalizeSignal :: Signal local -> Signal general
 

newtype ReactT ty m a Source

Constructors

ReactT 

Fields

runReactT :: AnimationState ty -> m ([ReactNode (Signal ty)], a)
 

Instances

Monad m => Monad (ReactT ty m) 
Monad m => Functor (ReactT ty m) 
Monad m => Applicative (ReactT ty m) 
(Monad m, (~) * a ()) => IsString (ReactT ty m a) 
(Monad m, Monoid a) => Monoid (ReactT ty m a) 

class ReactKey ty Source

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 state Double and can
-- emit SliderSignals.
pageFragment :: React Slider ()
pageFragment = div_ ...

-- this class stores the class state and animation state. its internals
-- can emit SliderSignals.
sliderClass :: ReactClass Slider ()
sliderClass = ...

Associated Types

type ClassState ty :: * Source

The state needed to render a class (ignoring animation)

type AnimationState ty :: * Source

The state needed to animate a class

type Signal ty :: * Source

The type of signals a class can send

Instances

newtype RenderHandle Source

Constructors

RenderHandle Int 

Instances

Unpack RenderHandle 
Pack RenderHandle 

data AnimConfig ty Source

Constructors

forall a . Animatable a => AnimConfig 

Fields

duration :: Double

How long this animation lasts in milliseconds

endpoints :: (a, a)

Where does this animation start and end?

lens :: Traversal' (AnimationState ty) a

Pointer to this field within AnimationState

easing :: Easing

How is the animation eased?

onComplete :: Bool -> Maybe (Signal ty)

Do something when it's finished?

data EventProperties e Source

Low level properties common to all events

Constructors

EventProperties 

Fields

bubbles :: !Bool
 
cancelable :: !Bool
 
currentTarget :: !e
 
defaultPrevented :: !Bool
 
eventPhase :: !Int
 
isTrusted :: !Bool
 
evtTarget :: !e
 
eventType :: !JSString
 

Instances

data KeyboardEvent Source

Constructors

KeyboardEvent 

Fields

keyboardModifierKeys :: !ModifierKeys
 
charCode :: !Int
 
key :: !JSString
 
keyCode :: !Int
 
locale :: !JSString
 
location :: !Int
 
repeat :: !Bool
 
which :: !Int
 

newtype ChangeEvent Source

Constructors

ChangeEvent 

Fields

targetValue :: JSString
 

data FocusEvent e Source

Constructors

FocusEvent 

Fields

domEventTarget :: !e
 
relatedTarget :: !e
 

Instances