Safe Haskell | None |
---|---|
Language | Haskell2010 |
React.Flux
Description
A binding to React based on the Flux design. The flux design pushes state and complicated logic out of the view, allowing the rendering functions and event handlers to be pure Haskell functions. When combined with React's composable components and the one-way flow of data, React, Flux, and GHCJS work very well together.
Prerequisites: This module assumes you are familiar with the basics of React and Flux. From the React documentation, you should read at least "Tutorial", "Displaying Data", "Multiple Components", and "Forms". Note that instead of JSX we use a Writer monad, but it functions very similarly so the examples in the React documentation are very similar to how you will write code using this module. The other React documentation you can skim, the Haddocks below link to specific sections of the React documentation when needed. Finally, you should read the Flux overview, in particular the central idea of one-way flow of data from actions to stores to views which produce actions.
Organization: Briefly, you should create one module to contain the dispatcher, one module for
each store, and modules for the view definitions. These are then imported into a Main module,
which calls reactRender
and initializes any AJAX load calls to the backend. The source package
contains an example TODO application.
Deployment: Care has been taken to make sure closure with ADVANCED_OPTIMIZATIONS correctly
minimizes a react-flux application. No externs are needed, instead all you need to do is provide
or protect the React
variable. The TODO example does this as follows:
(function(global, React) { contents of all.js })(this, window['React']);
Testing: I use the following approach to test my react-flux application. First, I use unit
testing to test the dispatcher and store transform
functions. Since the dispatcher and the
store transform are just data manipulation, existing Haskell tools like hspec, QuickCheck,
SmallCheck, etc. work well. Note that stores and dispatch
work in GHC and GHCJS, so this unit
testing can be done either in GHC or GHCJS. I don't do any unit testing of the views, because any
complicated logic in event handlers is moved into the dispatcher and the
rendering function is difficult to test in isolation. Instead, I test the rendering via
end-2-end tests using hspec-webdriver.
This tests the React frontend against the real backend and hspec-webdriver has many utilities for
easily checking that the DOM is what you expect. I have found this much easier than trying to
unit test each view individually, and you can still obtain the same coverage for equal effort.
The file test/spec/TodoSpec.hs
in the source code contains a hspec-webdriver test for the TODO example application.
- data ReactStore storeData
- class Typeable storeData => StoreData storeData where
- type StoreAction storeData
- transform :: StoreAction storeData -> storeData -> IO storeData
- mkStore :: StoreData storeData => storeData -> ReactStore storeData
- getStoreData :: ReactStore storeData -> IO storeData
- alterStore :: StoreData storeData => ReactStore storeData -> StoreAction storeData -> IO ()
- data SomeStoreAction = forall storeData . (StoreData storeData, NFData (StoreAction storeData)) => SomeStoreAction (ReactStore storeData) (StoreAction storeData)
- executeAction :: SomeStoreAction -> IO ()
- data ReactView props
- defineControllerView :: (StoreData storeData, Typeable props) => String -> ReactStore storeData -> (storeData -> props -> ReactElementM ViewEventHandler ()) -> ReactView props
- defineView :: Typeable props => String -> (props -> ReactElementM ViewEventHandler ()) -> ReactView props
- defineStatefulView :: (Typeable state, Typeable props) => String -> state -> (state -> props -> ReactElementM (StatefulViewEventHandler state) ()) -> ReactView props
- type ViewEventHandler = [SomeStoreAction]
- type StatefulViewEventHandler state = state -> ([SomeStoreAction], Maybe state)
- data ReactElement eventHandler
- newtype ReactElementM eventHandler a = ReactElementM {
- runReactElementM :: Writer (ReactElement eventHandler) a
- elemText :: String -> ReactElementM eventHandler ()
- elemShow :: Show a => a -> ReactElementM eventHandler ()
- view :: Typeable props => ReactView props -> props -> ReactElementM eventHandler a -> ReactElementM eventHandler a
- viewWithKey :: (Typeable props, ReactViewKey key) => ReactView props -> key -> props -> ReactElementM eventHandler a -> ReactElementM eventHandler a
- class ReactViewKey key
- childrenPassedToView :: ReactElementM eventHandler ()
- foreignClass :: JSRef cl -> [PropertyOrHandler eventHandler] -> ReactElementM eventHandler a -> ReactElementM eventHandler a
- module React.Flux.DOM
- module React.Flux.PropertiesAndEvents
- reactRender :: Typeable props => String -> ReactView props -> props -> IO ()
Dispatcher
The dispatcher is the central hub that manages all data flow in a Flux application. It has no
logic of its own and all it does is distribute actions to stores. There is no special support
for a dispatcher in this module, since it can be easily implemented directly using Haskell
functions. The event handlers registered during rendering are expected to produce a list of SomeStoreAction
.
The dispatcher therefore consists of Haskell functions which produce these lists of
SomeStoreAction
. Note that this list of actions is used instead of waitFor
to sequence
actions to stores: when dispatching, we wait for the transform
of each action to complete
before moving to the next action.
In the todo example application there is only a single store, so the dispatcher just passes along the action to the store. In a larger application, the dispatcher could have its own actions and produce specific actions for each store.
dispatchTodo :: TodoAction -> [SomeStoreAction] dispatchTodo a = [SomeStoreAction todoStore a]
Stores
data ReactStore storeData Source
A store contains application state, receives actions from the dispatcher, and notifies
component views to re-render themselves. You can have multiple stores; it should be the case
that all of the state required to render the page is contained in the stores. A store keeps a
global reference to a value of type storeData
, which must be an instance of StoreData
.
Stores also work when compiled with GHC instead of GHCJS. When compiled with GHC, the store is
just an MVar containing the store data and there are no controller views. alterStore
can still
be used, but it just transform
s the store and does not notify any controller-views since there
are none. Compiling with GHC instead of GHCJS can be helpful for unit testing, although GHCJS
plus node can also be used for unit testing.
data Todo = Todo { todoText :: String , todoComplete :: Bool , todoIsEditing :: Bool } deriving (Show, Typeable) newtype TodoState = TodoState { todoList :: [(Int, Todo)] } deriving (Show, Typeable) data TodoAction = TodoCreate String | TodoDelete Int | TodoEdit Int | UpdateText Int String | ToggleAllComplete | TodoSetComplete Int Bool | ClearCompletedTodos deriving (Show, Typeable, Generic, NFData) instance StoreData TodoState where type StoreAction TodoState = TodoAction transform action (TodoState todos) = ... todoStore :: ReactStore TodoState todoStore = mkStore $ TodoState [ (0, Todo "Learn react" True False) , (1, Todo "Learn react-flux" False False) ]
class Typeable storeData => StoreData storeData where Source
The data in a store must be an instance of this typeclass.
Methods
transform :: StoreAction storeData -> storeData -> IO storeData Source
Transform the store data according to the action. This is the only place in your app where
IO
should occur. The transform function should complete quickly, since the UI will not be
re-rendered until the transform is complete. Therefore, if you need to perform some longer
action, you should fork a thread from inside transform
. The thread can then call alterStore
with another action with the result of its computation. This is very common to communicate with
the backend using AJAX.
Note that if the transform throws an exception, the transform will be aborted and the old
store data will be kept unchanged. The exception will then be thrown from alterStore
.
For the best performance, care should be taken in only modifying the part of the store data that changed (see below for more information on performance).
mkStore :: StoreData storeData => storeData -> ReactStore storeData Source
Create a new store from the initial data.
getStoreData :: ReactStore storeData -> IO storeData Source
Obtain the store data from a store. Note that the store data is stored in an MVar, so
getStoreData
can block since it uses readMVar
. The MVar
is empty exactly when the store is
being transformed, so there is a possiblity of deadlock if two stores try and access each other's
data during transformation.
alterStore :: StoreData storeData => ReactStore storeData -> StoreAction storeData -> IO () Source
First, transform
the store data according to the given action. Next, if compiled with GHCJS,
notify all registered controller-views to re-render themselves. (If compiled with GHC, the store
data is just transformed since there are no controller-views.)
Only a single thread can be transforming the store at any one time, so this function will block
on an MVar
waiting for a previous transform to complete if one is in process.
data SomeStoreAction Source
An existential type for some store action. It is used as the output of the dispatcher.
The NFData
instance is important for performance, for details see below.
Constructors
forall storeData . (StoreData storeData, NFData (StoreAction storeData)) => SomeStoreAction (ReactStore storeData) (StoreAction storeData) |
Instances
executeAction :: SomeStoreAction -> IO () Source
Call alterStore
on the store and action.
Views
A view is conceptually a rendering function from props
and some internal state to a tree of elements. The function
receives a value of type props
from its parent in the virtual DOM. Additionally, the rendering
function can depend on some internal state or store data. Based on the props
and the internal
state, the rendering function produces a virtual tree of elements which React then reconciles
with the browser DOM.
This module supports 3 kinds of views. All of the views provided by this module are pure, in the
sense that the rendering function and event handlers cannot perform any IO. All IO occurs inside
the transform
function of a store.
Arguments
:: (StoreData storeData, Typeable props) | |
=> String | A name for this view, used only for debugging/console logging |
-> ReactStore storeData | The store this controller view should attach to. |
-> (storeData -> props -> ReactElementM ViewEventHandler ()) | The rendering function |
-> ReactView props |
A controller view provides the glue between a ReactStore
and the DOM.
The controller-view registers with the given store, and whenever the store is transformed the
controller-view re-renders itself. Each instance of a controller-view also accepts properties of
type props
from its parent. Whenever the parent re-renders itself, the new properties will be
passed down to the controller-view causing it to re-render itself.
Events registered on controller-views are expected to produce lists of SomeStoreAction
. Since
lists of SomeStoreAction
are the output of the dispatcher, each event handler should just be a
call to a dispatcher function. Once the event fires, the actions are executed causing the
store(s) to transform which leads to the controller-view(s) re-rendering. This one-way flow of
data from actions to store to controller-views is central to the flux design.
It is recommended to have one controller-view for each significant section of the page. Controller-views deeper in the page tree can cause complexity because data is now flowing into the page in multiple possibly conflicting places. You must balance the gain of encapsulated components versus the complexity of multiple entry points for data into the page. Note that multiple controller views can register with the same store.
todoApp :: ReactView () todoApp = defineControllerView "todo app" todoStore $ \todoState () -> div_ $ do todoHeader_ mainSection_ todoState todoFooter_ todoState
Arguments
:: Typeable props | |
=> String | A name for this view, used only for debugging/console logging |
-> (props -> ReactElementM ViewEventHandler ()) | The rendering function |
-> ReactView props |
A view is a re-usable component of the page which accepts properties of type props
from its
parent and re-renders itself whenever the properties change.
One option to implement views is to just use a Haskell function taking the props
as input and
producing a ReactElementM
. For small views, such a Haskell function is ideal.
Using a ReactView
provides more than just a Haskell function when used with a key property with
viewWithKey
. The key property allows React to more easily reconcile the virtual DOM with the
browser DOM.
The following is two example views: mainSection_
is just a Haskell function and todoItem
is a React view. We use the convention that an underscore suffix signifies a combinator
which can be used in the rendering function.
mainSection_ :: TodoState -> ReactElementM ViewEventHandler () mainSection_ st = section_ ["id" $= "main"] $ do input_ [ "id" $= "toggle-all" , "type" $= "checkbox" , "checked" $= if all (todoComplete . snd) $ todoList st then "checked" else "" , onChange $ \_ -> dispatchTodo ToggleAllComplete ] label_ [ "htmlFor" $= "toggle-all"] "Mark all as complete" ul_ [ "id" $= "todo-list" ] $ mapM_ todoItem_ $ todoList st todoItem :: ReactView (Int, Todo) todoItem = defineView "todo item" $ \(todoIdx, todo) -> li_ [ "className" @= (unwords $ [ "completed" | todoComplete todo] ++ [ "editing" | todoIsEditing todo ]) , "key" @= todoIdx ] $ do div_ [ "className" $= "view"] $ do input_ [ "className" $= "toggle" , "type" $= "checkbox" , "checked" @= todoComplete todo , onChange $ \_ -> dispatchTodo $ TodoSetComplete todoIdx $ not $ todoComplete todo ] label_ [ onDoubleClick $ \_ _ -> dispatchTodo $ TodoEdit todoIdx] $ elemText $ todoText todo button_ [ "className" $= "destroy" , onClick $ \_ _ -> dispatchTodo $ TodoDelete todoIdx ] mempty when (todoIsEditing todo) $ todoTextInput_ TextInputArgs { tiaId = Nothing , tiaClass = "edit" , tiaPlaceholder = "" , tiaOnSave = dispatchTodo . UpdateText todoIdx , tiaValue = Just $ todoText todo } todoItem_ :: (Int, Todo) -> ReactElementM eventHandler () todoItem_ todo = viewWithKey todoItem (fst todo) todo mempty
Arguments
:: (Typeable state, Typeable props) | |
=> String | A name for this view, used only for debugging/console logging |
-> state | The initial state |
-> (state -> props -> ReactElementM (StatefulViewEventHandler state) ()) | The rendering function |
-> ReactView props |
A stateful view is a re-usable component of the page which keeps track of internal state. Try to keep as many views as possible stateless. The React documentation on inteactivity and dynamic UIs has some discussion of what should and should not go into the state.
The rendering function is a pure function of the state and the properties from the parent. The view will be re-rendered whenever the state or properties change. The only way to transform the internal state of the view is via an event handler, which can optionally produce new state. Any more complicated state should be moved out into a (possibly new) store.
data TextInputArgs = TextInputArgs { tiaId :: Maybe String , tiaClass :: String , tiaPlaceholder :: String , tiaOnSave :: String -> [SomeStoreAction] , tiaValue :: Maybe String } deriving (Typeable) todoTextInput :: ReactView TextInputArgs todoTextInput = defineStatefulView "todo text input" "" $ \curText args -> input_ $ maybe [] (\i -> ["id" @= i]) (tiaId args) ++ [ "className" @= tiaClass args , "placeholder" @= tiaPlaceholder args , "value" @= curText , "autoFocus" @= True , onChange $ \evt _ -> ([], Just $ target evt "value") , onBlur $ \_ _ curState -> if not (null curState) then (tiaOnSave args curState, Just "") else ([], Nothing) , onKeyDown $ \_ evt curState -> if keyCode evt == 13 && not (null curState) -- 13 is enter then (tiaOnSave args curState, Just "") else ([], Nothing) ] todoTextInput_ :: TextInputArgs -> ReactElementM eventHandler () todoTextInput_ args = view todoTextInput args mempty
type ViewEventHandler = [SomeStoreAction] Source
Event handlers in a controller-view and a view transform events into actions, but are not
allowed to perform any IO
.
type StatefulViewEventHandler state = state -> ([SomeStoreAction], Maybe state) Source
A stateful-view event handler produces a list of store actions and potentially a new state. If the new state is nothing, no change is made to the state (which allows an optimization in that we do not need to re-render the view).
Changing the state causes a re-render which will cause a new event handler to be created. If the handler closes over the state passed into the rendering function, there is a race if multiple events occur before React causes a re-render. Therefore, the handler takes the current state as input. Your handlers therefore should ignore the state passed into the render function and instead use the state passed directly to the handler.
Elements
data ReactElement eventHandler Source
A React element is a node or list of nodes in a virtual tree. Elements are the output of the
rendering functions of classes. React takes the output of the rendering function (which is a
tree of elements) and then reconciles it with the actual DOM elements in the browser. The
ReactElement
is a monoid, so dispite its name can represent more than one element. Multiple
elements are rendered into the browser DOM as siblings.
Instances
Functor ReactElement Source | |
Monoid (ReactElement eventHandler) Source |
newtype ReactElementM eventHandler a Source
A writer monad for ReactElement
s which is used in the rendering function of all views.
do
notation or the Monoid
instance is used to sequence sibling elements.
Child elements are specified via function application; the combinator creating an element takes
the child element as a parameter. The OverloadedStrings
extension is used to create plain text.
ul_ $ do li_ (b_ "Hello") li_ "World" li_ $ ul_ (li_ "Nested" <> li_ "List")
would build something like
<ul> <li><b>Hello</b><li> <li>World</li> <li><ul> <li>Nested</li> <li>List</li> </ul></li> </ul>
The React.Flux.DOM module contains a large number of combinators for creating HTML elements.
Constructors
ReactElementM | |
Fields
|
Instances
(~) * child (ReactElementM eventHandler a) => Term eventHandler [PropertyOrHandler eventHandler] (child -> ReactElementM eventHandler a) Source | |
Term eventHandler (ReactElementM eventHandler a) (ReactElementM eventHandler a) Source | |
Monad (ReactElementM eventHandler) Source | |
Functor (ReactElementM eventHandler) Source | |
Applicative (ReactElementM eventHandler) Source | |
Foldable (ReactElementM eventHandler) Source | |
(~) * a () => IsString (ReactElementM eventHandler a) Source | |
(~) * a () => Monoid (ReactElementM eventHandler a) Source |
elemText :: String -> ReactElementM eventHandler () Source
Create a text element from a string. This is an alias for fromString
. The text content is
escaped to be HTML safe. If you need to insert HTML, instead use the
dangerouslySetInnerHTML
property.
elemShow :: Show a => a -> ReactElementM eventHandler () Source
Create an element containing text which is the result of show
ing the argument.
Note that the resulting string is then escaped to be HTML safe.
Arguments
:: Typeable props | |
=> ReactView props | the view |
-> props | the properties to pass into the instance of this view |
-> ReactElementM eventHandler a | The children of the element |
-> ReactElementM eventHandler a |
Create an element from a view. I suggest you make a combinator for each of your views, similar
to the examples above such as todoItem_
.
Arguments
:: (Typeable props, ReactViewKey key) | |
=> ReactView props | the view |
-> key | A value unique within the siblings of this element |
-> props | The properties to pass to the view instance |
-> ReactElementM eventHandler a | The children of the view |
-> ReactElementM eventHandler a |
Create an element from a view, and also pass in a key property for the instance. Key properties speed up the reconciliation of the virtual DOM with the DOM. The key does not need to be globally unqiue, it only needs to be unique within the siblings of an element.
class ReactViewKey key Source
Keys in React can either be strings or integers
Minimal complete definition
Instances
childrenPassedToView :: ReactElementM eventHandler () Source
Transclude the children passed into view
or viewWithKey
into the
current rendering. Use this where you would use this.props.children
in a javascript React
class.
Arguments
:: JSRef cl | The javascript reference to the class |
-> [PropertyOrHandler eventHandler] | properties and handlers to pass when creating an instance of this class. |
-> ReactElementM eventHandler a | The child element or elements |
-> ReactElementM eventHandler a |
Create a ReactElement
for a class defined in javascript. For example, if you would like to
use react-select, you could do so as follows:
foreign import javascript unsafe "window['Select']" js_ReactSelectClass :: JSRef () reactSelect_ :: [PropertyOrHandler eventHandler] -> ReactElementM eventHandler () reactSelect_ props = foreignClass js_ReactSelectClass props mempty onSelectChange :: FromJSON a => (a -> handler) -- ^ receives the new value and performs an action. -> PropertyOrHandler handler onSelectChange f = callback "onChange" (f . parse) where parse v = case fromJSON v of Error err -> error $ "Unable to parse new value for select onChange: " ++ err Success e -> e
This could then be used as part of a rendering function like so:
reactSelect_ [ "name" $= "form-field-name" , "value" $= "one" , "options" @= [ object [ "value" .= "one", "label" .= "One" ] , object [ "value" .= "two", "label" .= "Two" ] ] , onSelectChange dispatchSomething ]
module React.Flux.DOM
Main
Arguments
:: Typeable props | |
=> String | The ID of the HTML element to render the application into.
(This string is passed to |
-> ReactView props | A single instance of this view is created |
-> props | the properties to pass to the view |
-> IO () |
Render your React application into the DOM.
Performance
React obtains high performance from two techniques: the virtual DOM/reconciliation and event handlers registered on the document.
To support fast reconciliation, React uses key properties (set by viewWithKey
) and a
shouldComponentUpdate
lifetime class method. The React documentation on
performance and immutable-js talks
about using persistent data structures, which is exactly what Haskell does. Therefore, we
implement a shouldComponentUpdate
method which compares if the javascript object representing
the Haskell values for the props
, state
, and/or storeData
have changed. Thus if you do not
modify a Haskell value that is used for the props
or state
or storeData
, React will skip
re-rendering that view instance. Care should be taken in the transform
function to not edit or
recreate any values that are used as props
. For example, instead of something like
[ (idx, todo) | (idx, todo) <- todos, idx /= deleteIdx ]
you should prefer
filter ((/=deleteIdx) . fst) todos
After either of these transforms, the list of todos has changed so mainSection
will be re-rendered by
React. mainSection
calls todoItem
with the tuple (idx,todo)
as the props. In the latter
transform snippet above, the tuple value for the entries is kept unchanged, so the
shouldComponentUpdate
function for todoItem
will return false and React will not re-render
each todo item. If instead the tuple had been re-created as in the first snippet, the underlying
javascript object will change even though the value is equal. The shouldComponentUpdate
function for todoItem
will then return true and React will re-render every todo item. Thus the
latter snippet is preferred. In summary, if you are careful to only update the part of the store
data that changed, React will only re-render those part of the page.
For events, React registers only global event handlers and also keeps event objects (the object
passed to the handlers) in a pool and re-uses them for successive events. We want to parse this
event object lazily so that only properties actually accessed are parsed, but this is a problem
because lazy access could occur after the event object is reused. Instead of making a copy of
the event, we use the NFData
instance on SomeStoreAction
to force the evaluation of the store
action(s) resulting from the event. We therefore compute the action before the event object
returns to the React pool, and rely on the type system to prevent the leak of the event object
outside the handlers. Thus, you cannot "cheat" in the NFData
instance on your store actions;
the event objects dilerbertly do not have a NFData
instance, so that you must pull all your
required data out of the event object and into an action in order to properly implement NFData
.
Of course, the easiest way to implement NFData
is to derive it with Generic and DeriveAnyClass,
as TodoAction
does above.