Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal module for React.Flux
Normally you should not need to use anything in this module. This module is only needed if you have complicated interaction with third-party javascript rendering code.
- newtype ReactViewRef props = ReactViewRef {
- reactViewRef :: JSVal
- class ReactViewKey key where
- newtype ReactElementRef = ReactElementRef {
- reactElementRef :: JSVal
- newtype HandlerArg = HandlerArg JSVal
- data PropertyOrHandler handler
- = forall ref . ToJSVal ref => Property {
- propertyName :: String
- propertyVal :: ref
- | forall ref . ToJSVal ref => PropertyFromContext {
- propFromThisName :: String
- propFromThisVal :: JSVal -> ref
- | NestedProperty {
- nestedPropertyName :: String
- nestedPropertyVals :: [PropertyOrHandler handler]
- | ElementProperty {
- elementPropertyName :: String
- elementValue :: ReactElementM handler ()
- | CallbackPropertyWithArgumentArray {
- caPropertyName :: String
- caFunc :: JSArray -> IO handler
- | CallbackPropertyWithSingleArgument {
- csPropertyName :: String
- csFunc :: HandlerArg -> handler
- = forall ref . ToJSVal ref => Property {
- property :: ToJSVal val => String -> val -> PropertyOrHandler handler
- data ReactElement eventHandler
- = ForeignElement {
- fName :: Either String (ReactViewRef Object)
- fProps :: [PropertyOrHandler eventHandler]
- fChild :: ReactElement eventHandler
- | forall props key . (Typeable props, ReactViewKey key) => ViewElement {
- ceClass :: ReactViewRef props
- ceKey :: Maybe key
- ceProps :: props
- ceChild :: ReactElement eventHandler
- | ChildrenPassedToView
- | Content String
- | Append (ReactElement eventHandler) (ReactElement eventHandler)
- | EmptyElement
- = ForeignElement {
- newtype ReactElementM eventHandler a = ReactElementM {
- runReactElementM :: Writer (ReactElement eventHandler) a
- elemText :: String -> ReactElementM eventHandler ()
- elemShow :: Show a => a -> ReactElementM eventHandler ()
- el :: String -> [PropertyOrHandler eventHandler] -> ReactElementM eventHandler a -> ReactElementM eventHandler a
- childrenPassedToView :: ReactElementM eventHandler ()
- elementToM :: a -> ReactElement eventHandler -> ReactElementM eventHandler a
- mkReactElement :: forall eventHandler. (eventHandler -> IO ()) -> IO JSVal -> IO [ReactElementRef] -> ReactElementM eventHandler () -> IO (ReactElementRef, [Callback (JSVal -> IO ())])
- toJSString :: String -> String
Documentation
newtype ReactViewRef props Source
This type is for the return value of React.createClass
ReactViewRef | |
|
class ReactViewKey key where Source
Keys in React can either be strings or integers
newtype ReactElementRef Source
This type is for the return value of React.createElement
ReactElementRef | |
|
newtype HandlerArg Source
The first parameter of an event handler registered with React.
HandlerArg JSVal |
data PropertyOrHandler handler Source
Either a property or an event handler.
The combination of all properties and event handlers are used to create the javascript object
passed as the second argument to React.createElement
.
forall ref . ToJSVal ref => Property | |
| |
forall ref . ToJSVal ref => PropertyFromContext | |
| |
NestedProperty | |
| |
ElementProperty | |
| |
CallbackPropertyWithArgumentArray | |
| |
CallbackPropertyWithSingleArgument | |
|
Functor PropertyOrHandler Source | |
(~) * child (ReactElementM eventHandler a) => Term eventHandler [PropertyOrHandler eventHandler] (child -> ReactElementM eventHandler a) Source |
property :: ToJSVal val => String -> val -> PropertyOrHandler handler Source
Create a property from anything that can be converted to a JSVal
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.
ForeignElement | |
| |
forall props key . (Typeable props, ReactViewKey key) => ViewElement | |
| |
ChildrenPassedToView | |
Content String | |
Append (ReactElement eventHandler) (ReactElement eventHandler) | |
EmptyElement |
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.
ReactElementM | |
|
(~) * 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.
:: String | The element name (the first argument to |
-> [PropertyOrHandler eventHandler] | The properties to pass to the element (the second argument to |
-> ReactElementM eventHandler a | The child elements (the third argument to |
-> ReactElementM eventHandler a |
Create a React element.
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.
elementToM :: a -> ReactElement eventHandler -> ReactElementM eventHandler a Source
Create a ReactElementM
containing a given ReactElement
.
:: (eventHandler -> IO ()) | |
-> IO JSVal | this.context |
-> IO [ReactElementRef] | this.props.children |
-> ReactElementM eventHandler () | |
-> IO (ReactElementRef, [Callback (JSVal -> IO ())]) |
Execute a ReactElementM to create a javascript React element and a list of callbacks attached
to nodes within the element. These callbacks will need to be released with releaseCallback
once the class is re-rendered.
toJSString :: String -> String Source