react-flux-1.2.3: A binding to React based on the Flux application architecture for GHCJS

Safe HaskellNone
LanguageHaskell2010

React.Flux

Contents

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 some example applications.

Web Deployment: reactRender is used to render your application into the DOM. 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 protect the React variable (and ReactDOM if you are using version >= 0.14). The TODO example does this as follows:

(function(global, React, ReactDOM) {
contents of all.js
})(window, window['React'], window['ReactDOM']);

Node Deployment: reactRenderToString is used to render the application to a string when running in node (not the browser). To execute with node, you need to get global.React and global.ReactDOMServer before executing all.js. The TODO example application does this by creating a file run-in-node.js with the contents

React = require("react");
ReactDOMServer = require("react-dom/server");
require("../../js-build/install-root/bin/todo-node.jsexe/all.js");

React Native: This module also works with React-Native to create a standalone native applications. When combined with electron, you can even create standalone desktop applications. The workflow is to use reactRender the same as web deployment but use the resulting JavaScript file in react-native and/or electron. Jyrimatti has an example using react-native.

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.

Synopsis

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 controller-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 transforms 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 :: Text
  , todoComplete :: Bool
  , todoIsEditing :: Bool
} deriving (Show, Typeable)

newtype TodoState = TodoState {
    todoList :: [(Int, Todo)]
} deriving (Show, Typeable)

data TodoAction = TodoCreate Text
                | TodoDelete Int
                | TodoEdit Int
                | UpdateText Int Text
                | 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.

Minimal complete definition

transform

Associated Types

type StoreAction storeData Source #

The actions that this store accepts

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. Indeed, the jsonAjax utility function implements exactly this strategy since it is so common.

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

(StoreData storeData, NFData (StoreAction storeData)) => SomeStoreAction (ReactStore storeData) (StoreAction storeData) 

executeAction :: SomeStoreAction -> IO () Source #

Call alterStore on the store and action.

Views

data ReactView props Source #

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.

Due to React limitations (see issue2127), React views must have a single top-level element. If your haskell code returns multiple top-level elements, react-flux will wrap them in a container div. You should not rely on this and instead make sure each view returns only a single top-level element (such as todoItem below returning only a single li element).

defineControllerView Source #

Arguments

:: (StoreData storeData, Typeable props) 
=> JSString

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

defineView Source #

Arguments

:: Typeable props 
=> JSString

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 viewWithSKey and viewWithIKey. 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_ [ classNames [("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 = viewWithIKey todoItem (fst todo) todo mempty

defineStatefulView Source #

Arguments

:: (Typeable state, NFData state, Typeable props) 
=> JSString

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 interactivity 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 JSString
    , tiaClass :: JSString
    , tiaPlaceholder :: JSString
    , tiaOnSave :: Text -> [SomeStoreAction]
    , tiaValue :: Maybe Text
} 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 (Text.null curState)
                 then (tiaOnSave args curState, Just "")
                 else ([], Nothing)
        , onKeyDown $ \_ evt curState ->
             if keyCode evt == 13 && not (Text.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 # 

Methods

fmap :: (a -> b) -> ReactElement a -> ReactElement b #

(<$) :: a -> ReactElement b -> ReactElement a #

Monoid (ReactElement eventHandler) Source # 

Methods

mempty :: ReactElement eventHandler #

mappend :: ReactElement eventHandler -> ReactElement eventHandler -> ReactElement eventHandler #

mconcat :: [ReactElement eventHandler] -> ReactElement eventHandler #

newtype ReactElementM eventHandler a Source #

A writer monad for ReactElements 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 # 

Methods

term :: JSString -> [PropertyOrHandler eventHandler] -> child -> ReactElementM eventHandler a Source #

Term eventHandler (ReactElementM eventHandler a) (ReactElementM eventHandler a) Source # 

Methods

term :: JSString -> ReactElementM eventHandler a -> ReactElementM eventHandler a Source #

Monad (ReactElementM eventHandler) Source # 

Methods

(>>=) :: ReactElementM eventHandler a -> (a -> ReactElementM eventHandler b) -> ReactElementM eventHandler b #

(>>) :: ReactElementM eventHandler a -> ReactElementM eventHandler b -> ReactElementM eventHandler b #

return :: a -> ReactElementM eventHandler a #

fail :: String -> ReactElementM eventHandler a #

Functor (ReactElementM eventHandler) Source # 

Methods

fmap :: (a -> b) -> ReactElementM eventHandler a -> ReactElementM eventHandler b #

(<$) :: a -> ReactElementM eventHandler b -> ReactElementM eventHandler a #

Applicative (ReactElementM eventHandler) Source # 

Methods

pure :: a -> ReactElementM eventHandler a #

(<*>) :: ReactElementM eventHandler (a -> b) -> ReactElementM eventHandler a -> ReactElementM eventHandler b #

(*>) :: ReactElementM eventHandler a -> ReactElementM eventHandler b -> ReactElementM eventHandler b #

(<*) :: ReactElementM eventHandler a -> ReactElementM eventHandler b -> ReactElementM eventHandler a #

Foldable (ReactElementM eventHandler) Source # 

Methods

fold :: Monoid m => ReactElementM eventHandler m -> m #

foldMap :: Monoid m => (a -> m) -> ReactElementM eventHandler a -> m #

foldr :: (a -> b -> b) -> b -> ReactElementM eventHandler a -> b #

foldr' :: (a -> b -> b) -> b -> ReactElementM eventHandler a -> b #

foldl :: (b -> a -> b) -> b -> ReactElementM eventHandler a -> b #

foldl' :: (b -> a -> b) -> b -> ReactElementM eventHandler a -> b #

foldr1 :: (a -> a -> a) -> ReactElementM eventHandler a -> a #

foldl1 :: (a -> a -> a) -> ReactElementM eventHandler a -> a #

toList :: ReactElementM eventHandler a -> [a] #

null :: ReactElementM eventHandler a -> Bool #

length :: ReactElementM eventHandler a -> Int #

elem :: Eq a => a -> ReactElementM eventHandler a -> Bool #

maximum :: Ord a => ReactElementM eventHandler a -> a #

minimum :: Ord a => ReactElementM eventHandler a -> a #

sum :: Num a => ReactElementM eventHandler a -> a #

product :: Num a => ReactElementM eventHandler a -> a #

(~) * a () => IsString (ReactElementM eventHandler a) Source # 

Methods

fromString :: String -> ReactElementM eventHandler a #

(~) * a () => Monoid (ReactElementM eventHandler a) Source # 

Methods

mempty :: ReactElementM eventHandler a #

mappend :: ReactElementM eventHandler a -> ReactElementM eventHandler a -> ReactElementM eventHandler a #

mconcat :: [ReactElementM eventHandler a] -> ReactElementM eventHandler a #

elemString :: String -> ReactElementM eventHandler () Source #

Create a text element from a string. The text content is escaped to be HTML safe. If you need to insert HTML, instead use the dangerouslySetInnerHTML property. This is an alias for fromString.

elemText :: Text -> ReactElementM eventHandler () Source #

Create a text element from a text value. The text content is escaped to be HTML safe.

elemJSString :: JSString -> ReactElementM eventHandler () Source #

Create a text element from a JSString. This is more efficient for hard-coded strings than converting from text to a JavaScript string. The string is escaped to be HTML safe.

elemShow :: Show a => a -> ReactElementM eventHandler () Source #

Create an element containing text which is the result of showing the argument. Note that the resulting string is then escaped to be HTML safe.

view Source #

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_.

viewWithSKey Source #

Arguments

:: Typeable props 
=> ReactView props

the view

-> JSString

The 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 string 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.

viewWithIKey Source #

Arguments

:: Typeable props 
=> ReactView props

the view

-> Int

The 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 

Similar to viewWithSKey, but with an integer key instead of a string key.

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.

foreignClass Source #

Arguments

:: JSVal

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. See foreign_ for a convenient wrapper and some examples.

rawJsRendering Source #

Arguments

:: (JSVal -> JSArray -> IO JSVal)

The raw code to inject into the rendering function. The first argument is the this value from the rendering function so points to the react class. The second argument is the result of rendering the children so is an array of react elements. The return value must be a React element.

-> ReactElementM handler ()

the children

-> ReactElementM handler () 

Inject arbitrary javascript code into the rendering function. This is very low level and should only be used as a last resort when interacting with complex third-party react classes. For the most part, third-party react classes can be interacted with using foreignClass and the various ways of creating properties.

transHandler :: (handler1 -> handler2) -> ReactElementM handler1 a -> ReactElementM handler2 a Source #

Transform the event handler for a ReactElementM.

liftViewToStateHandler :: ReactElementM ViewEventHandler a -> ReactElementM (StatefulViewEventHandler st) a Source #

Change the event handler from ViewEventHandler to StatefulViewEventHandler to allow you to embed combinators with ViewEventHandlers into a stateful view. Each such lifted handler makes no change to the state.

Main

reactRender Source #

Arguments

:: Typeable props 
=> String

The ID of the HTML element to render the application into. (This string is passed to document.getElementById)

-> 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. Use this from your main function, and only in the browser. reactRender only works when compiled with GHCJS (not GHC), because we rely on the React javascript code to actually perform the rendering.

reactRenderToString Source #

Arguments

:: Typeable props 
=> Bool

Render to static markup? If true, this won't create extra DOM attributes that React uses internally.

-> ReactView props

A single instance of this view is created

-> props

the properties to pass to the view

-> IO Text 

Render your React application to a string using either ReactDOMServer.renderToString if the first argument is false or ReactDOMServer.renderToStaticMarkup if the first argument is true. Use this only on the server when running with node. reactRenderToString only works when compiled with GHCJS (not GHC), because we rely on the React javascript code to actually perform the rendering.

If you are interested in isomorphic React, I suggest instead of using reactRenderToString you use exportViewToJavaScript and then write a small top-level JavaScript view which can then integrate with all the usual isomorphic React tools.

exportViewToJavaScript :: (Typeable props, ArgumentsToProps props func) => ReactView props -> func -> IO JSVal Source #

Export a Haskell view to a JavaScript function. This allows you to embed a Haskell react-flux application into a larger existing JavaScript React application. If you want to use JavaScript classes in your Haskell application, you should instead use foreign_ and foreignClass.

The way this works is as follows:

  1. You create a Haskell function which translates the javascript arguments of into a Haskell value of type ReturnProps props. This is a variable-argument function using the ArgumentsToProps class. For example,

     data MyProps = MyProps { theInt :: Int, theString :: String }
     myArgsToProps :: Int -> String -> ReturnProps MyProps
     myArgsToProps i s = ReturnProps $ MyProps i s
     
  2. You create a view which receives these properties and renders itself. This view will not receive any children.

     myView :: ReactView MyProps
     myView = defineView "my view" $ \myProps -> ...
     
  3. You can then use exportViewToJavaScript to create a JavaScript function. When this JavaScript function is executed, the JavaScript arguments are converted to the props, the view is rendered using the props, and the resulting React element is returned from the JavaScript function.

     foreign import javascript unsafe
         "window['myHaskellView'] = $1;"
         js_setMyView :: JSVal -> IO ()
    
     exportMyView :: IO ()
     exportMyView = exportViewToJavaScript myView myArgsToProps >>= js_setMyView
     

    exportMyView should be called from your main function. After executing exportMyView, the window.myHaskellView property will be a javascript function.

  4. Call the javascript function with two arguments to return a React element which can be used in a JavaScript React class rendering function.
      var myJsView = React.createClass({
          render: function() {
              return <div>{window.myHaskellView(5, "Hello World")}</div>;
          }
      };
      

class ArgumentsToProps props a | a -> props Source #

A class which is used to implement variable argument functions. These variable argument functions are used to convert from a JavaScript arguments array to a Haskell value of type props.

Any function where each argument implements FromJSVal and the result is ReturnProps is an instance of this class. Entries from the JavaScript arguments array are matched one-by-one to the arguments before ReturnProps value. If the Haskell function has more parameters than the javascript arguments object, a javascript null is used for the conversion. Since the Maybe instance of FromJSVal converts null references to Nothing, you can exploit this to handle arguments not given to the JavaScript function.

Minimal complete definition

returnViewFromArguments

Instances

ArgumentsToProps props (ReturnProps props) Source # 

Methods

returnViewFromArguments :: JSArray -> Int -> ReturnProps props -> IO props

(FromJSVal a, ArgumentsToProps props b) => ArgumentsToProps props (a -> b) Source # 

Methods

returnViewFromArguments :: JSArray -> Int -> (a -> b) -> IO props

newtype ReturnProps props Source #

A type needed to make GHC happy when solving for instances of ArgumentsToProps.

Constructors

ReturnProps props 

Instances

ArgumentsToProps props (ReturnProps props) Source # 

Methods

returnViewFromArguments :: JSArray -> Int -> ReturnProps props -> IO props

Performance

React obtains high performance from two techniques: the virtual DOM/reconciliation and event handlers registered on the document.

Reconciliation

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. Note that we are not checking equality, just if the javascript object representing a Haskell object has changed, with some special support for pairs and tuples of size three.

There is subtle issue: this check only works if the props are not a thunk but are an actual data constructor. Consider the following

data MyStoreData = MyStoreData {
   myA :: !A
 , myB :: !B
 , myC :: !C
 , myD :: !D
} deriving (Show, Typeable)

myAview :: ReactView A
myAview = defineView ....

myStoreView :: ReactView ()
myStoreView = defineControllerView "my store" myStore $ \myData () ->
    div_ $ view myAview (myA myData) mempty
    div_ ....

In myStoreView, note that myA myData is passed as the props to myAview. So consider the situtation when say an action changes C but leaves A unchanged. We would like for the rendering of myAview to be skipped, but unfortunately it will be re-rendered. The reason is that the props passed to myAview is an unevaluated thunk myA myData. Sure, the A constructor has not changed and if the thunk is forced it will return this unchanged A data constructor, but the shouldComponentUpdate test does not do any computation or evaluation, it just checks if the passed in javascript object is the same as it was the last time the view was rendered. We can fix this by forcing the thunk before passing it to view, which I do via bang patterns. Instead of ever calling view directly from a rendering function, for each ReactView I create a combinator as follows:

myAview_ :: A -> ReactElementM handler ()
myAview_ !a = view myAview a mempty

myStoreView :: ReactView ()
myStoreView = defineControllerView "my store" myStore $ \myData () ->
    div_ $ myAview_ (myA myData)
    div_ ....

Note the bang pattern on the a parameter to myAview_. What now happens is that the bang pattern forces the thunk myA myData to turn into the A data constructor. If an action does not edit the A portion of the store data, this will still be represented by the same javascript object as before and React will not re-render the myAview.

Now consider another situtation where you would like a view that takes A and B.

myAandBview :: ReactView (A, B)
myAandBview = defineView ....

myAandBview_ :: A -> B -> ReactElementM handler ()
myAandBview_ !a !b = view myAandBview (a, b) mempty

myStoreView :: ReactView ()
myStoreView = defineControllerView "my store" myStore $ \myData () ->
    div_ $ myAview_ (myA myData)
    div_ $ myAandBview_ (myA myData) (myB myData)
    div_ ....

Again, if you have an action that just changes C you would like myAandBview to not be re-rendered. With the simple javascript object check, it would be re-rendered because the props are a tuple and the Haskell value (and thus javascript object) for the tuple is being recreated each time myStoreView is rendered. To overcome this obstacle, react-flux contains special code to check pairs and tuples of size three. If the props are a pair or a tuple of size three, the components of the tuple will be compared to see if they are the same javascript object. Thus similar to the above we need to make sure each component of the tuple is not a thunk but a data constructor, which happens via the bang patterns in myAandBview_. The end result is that if an action just changes C or D and leaves A and B unchanged, the above code will cause React to not re-render myAandBview because the two components of the pair are forced and are still the same unchanged data value/javascript object. You can see this in action inside the test suite if you would like an example.

So far we have been focusing on making sure the new props are not a thunk by forcing it before passing it into view. But we also need to make sure the initial props are not a thunk. This is not quite as bad since the check will only fail the next time a re-render occurs and after that everything will be OK so we will still mostly skip re-rendering, but is still a small annoyance. There are several ways to fix this, but the easiest is to add bang patterns to the definition of MyStoreData. If you scroll up you can see that each member of MyStoreData has a bang pattern. Thus when an action does change A, whatever a new value is set into myA, it will not be a thunk but an actual data constructor. Then the initial props passed into the view will not be a thunk.

In summary, you should follow these rules:

  1. Use bang patterns on each member in your store data. In fact, once GHC 8 is released, I plan on turning on the new StrictData extension and then all these bang patterns can be dropped.
  2. Try and keep your view parameters as part of the store that will be unchanged by some actions. Use tuples of size two or three to combine multiple parts of the store data or even data from multiple stores. (Tuples of larger size could be supported without much effort if required.)
  3. For each view, make a combinator with a underscore suffix which uses bang patterns to force the props before passing it to the view function.

Events

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.

Depracated

viewWithKey Source #

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 

A deprecated way to create a view with a key which has problems when OverloadedStrings is active. Use viewWithSKey or viewWithIKey instead.

class ReactViewKey key Source #

Keys in React can either be strings or integers

Minimal complete definition

toKeyRef

Instances

ReactViewKey Int Source # 

Methods

toKeyRef :: Int -> JSVal

ReactViewKey String Source # 

Methods

toKeyRef :: String -> JSVal