This is a library of reusable composable widget using
Glazier.React
. Please help me to add more widgets to this library!
Prerequisite reading
Glazier
Please read the README.md for a brief overview of glazier.
Glazier.React
Please read the README.md for a brief overview of glazier-react.
The following documents the expected conventions and best practices when defining a Glazier.React.Widgets
widget.
Exports
All widgets should export at the minimum the following:
module Glazier.React.Widgets.Input
( Command(..)
, Action(..)
, AsAction(..)
, Design(..)
, HasDesign(..)
, Plan(..)
, HasPlan(..)
, Outline
, Model
, Widget
, widget
) where
This provides a consistent way to interact and use every widget.
Since all widgets export the same names, any widget should be imported qualified.
Command
Command
s are the result of the Gadget
stateful processing of Action
. It is a pure value that is interpreted effectfully.
data Command
= RenderCommand (SuperModel Model Plan) [Property] JSVal
| DisposeCommand SomeDisposable
| MakerCommand (F (Maker Action) Action)
Some common commands are:
RenderCommand
RenderCommand (SuperModel Model Plan) [Property] JSVal
This is send by Gadget
when the re-rendering is required. It contains theSuperModel
of the widget (to swap the latest Design
into the Frame
), the new React component state as a list of properties (usually just a sequence number), and the javascript reference to the javascript component.
DisposeCommand
DisposeCommand SomeDisposable
This contains the list of callbacks to dispose after the next render frame (after componentDidUpdate
is called.
MakerCommand
MakerCommand (F (Maker Action) Action)
This is the command to run the Maker
instruction in the Maker
interpreter which results in an Action
to outcome back tot he gadget.
Action
This contains the events that the widget Gadget
processes.
data Action
= ComponentRefAction JSVal
| RenderAction
| ComponentDidUpdateAction
makeClassyPrisms ''Action
Action
s should have makeClassyPrisms
generated to facilitate embedding it in larger Gadget
with magnify
.
Some common Action
s are:
ComponentRefAction
ComponentRefAction JSVal
This action is generated by the ref
event listener and contains a javascript reference to the react component. This ref is used in the RenderCommand
.
RenderAction
RenderAction
You can generate this action to force a widget to return the RenderCommand
to force a re-render.
ComponentDidUpdateAction
ComponentDidUpdateAction JSVal
This action is generated by the componentDidUpdate
event listener. This event is usually used to generate the DisposeCommand
to dispose callbacks from removed widgets.
Design
This contains the template for pure data for state processing logic (the nouns).
data Design = Design
{ _blah :: Foo
}
makeClassy ''Design
type Model = Design
type Outline = Design
instance ToOutline Model Outline where outline = id
mkModel :: Outline -> F (Maker Action) Model
mkModel = pure
Design
s should have makeClassy
generated to facilitate embedding it in larger widget with magnify
and zoom
.
If the Design
contains child widgets, then it should have use a type parameter and DesignType
to allow specializations of Model
and Outline
data Design t = Design
{ _input :: DesignType t W.Input.Widget
, _todos :: DesignType t (W.List.Widget TodosKey TD.Todo.Widget)
, _footer :: DesignType t TD.Footer.Widget
}
type Model = Design WithGizmo
type Outline = Design WithOutline
instance ToOutline Model Outline where
outline (Design a b c) = Design (outline a) (outline b) (outline c)
mkModel :: ReactMl () -> Outline -> F (Maker Action) Model
mkModel separator (Design a b c) = Design
<$> (hoistWithAction InputAction (mkGizmo' W.Input.widget a))
<*> (hoistWithAction TodosAction (mkGizmo' (W.List.widget separator TD.Todo.widget) b))
<*> (hoistWithAction FooterAction (mkGizmo' TD.Footer.widget c))
Plan
The Plan
contains the callbacks for integrating with React (the verbs). It also contains a javascript reference to the instance of shim component used for the widget. This reference is used to trigger rendering with setState
.
data Plan = Plan
{ _component :: ReactComponent
, _key :: J.JSString
, _frameNum :: Int
, _componentRef :: J.JSVal
, _deferredDisposables :: D.DList CD.SomeDisposable
, _onRender :: J.Callback (J.JSVal -> IO J.JSVal)
, _onComponentRef :: J.Callback (J.JSVal -> IO ())
, _onComponentDidUpdate :: J.Callback (J.JSVal -> IO ()) makeClassy ''Plan
Plan
s should have makeClassy
generated to allow consistent usage of lens to access Model
and Plan
fields.
Some common Plan
fields are
key
_key :: JSString
key
is used to ensure a unique key for React's efficient rendering of a list.
componentRef
_componentRef :: JSVal
componentRef
is used to store the reference to the instance of the React shim component from the ComponentRefAction
and used in the RenderCommand
_frameNum :: Int
frameNum
is the sequence number used in RenderCommand
.
_deferredDisposables
_deferredDisposables :: DList SomeDisposable
deferredDisposables
keep the list of disposables to dispose at the next ComponentDidUpdateAction
.
_component
_component :: ReactComponent
This contains the reference to the shim React.PureComponent
class that is used to start the rendering.
_onRender
_onRender :: Callback (JSVal -> IO JSVal)
The is the callback from the shim component's render
handler. It contains a javascript reference to the shim component's state, which is currently not used, but might be in the future.
_onComponentRef
_onComponentRef :: Callback (JSVal -> IO ())
The is the callback from the shim component's ref
event listener. The callback is expected to generate the ComponentRefAction
.
_onComponentDidUpdate
_onComponentDidUpdate :: Callback (JSVal -> IO ())
The is the callback from the shim component's componentDidUpdate
event listener. The callback is expected to generate the ComponentDidUpdateAction
.
mkPlan
This is the missing piece required to construct a widget's SuperModel
.
It contains the code to create a widget's Plan
using the Maker
DSL.
The Applicative
typeclass makes this easy to define.
mkPlan :: Frame Model Plan -> F (Maker Action) Plan
mkPlan frm = Plan
<$> getComponent
<*> mkKey
<*> pure 0
<*> pure J.nullRef
<*> pure mempty
<*> (mkRenderer frm $ const render)
<*> (mkHandler $ pure . pure . InputRefAction)
<*> (mkHandler $ pure . pure . ComponentRefAction)
<*> (mkHandler $ pure . pure . const ComponentDidUpdateAction)
Common code
All widgets should have implementation of the following
Disposing Model and Plan
instance Disposing Plan
instance Disposing Model where
disposing _ = DisposeNone
Link HasPlan and HasModel
Link Glazier.React.Model
's genericHasPlan/HasModel with this widget's specific HasPlan
/HasModel
from generated from makeClassy
instance HasPlan (Scene Model Plan) where
plan = plan
instance HasDesign (Scene Model Plan) where
design = model
instance HasPlan (Gizmo Model Plan) where
plan = scene . plan
instance HasDesign (Gizmo Model Plan) where
design = scene . design
widget
is a record of functions of the essential functions required to make, render and interact with the widget. By convention, mkPlan
, window
, and gadget
is exported, but sometimes it's convenient to have all three grouped together in a record.
type Widget = Widget Command Action Model Plan
widget :: Widget
widget = Widget
mkModel
mkPlan
window
gadget
widget
is always an instance of IsWidget
typeclass, so exporting a type synomym Widget
will allow generic widget manipulation code.
For example, the List
widget uses the IsWidget
typeclass of the item widgets in order to define the widget
record value.
window
This is the starting rendering function to start the rendering. It always only renders the shim React component with the specific callbacks:
window :: WindowT (Design Model Plan) ReactMl ()
window = do
s <- ask
lift $ lf (s ^. component . to toJS)
[ ("key", s ^. key . to toJS)
, ("render", s ^. onRender . to toJS)
, ("ref", s ^. onComponentRef . to toJS)
, ("componentDidUpdate", s ^. onComponentDidUpdate . to toJS)
]
This a a monad transformer stack over Identity
. This ensures only pure effects are allowed.
render
This is the inner rendering function. React will render the shim component from window
above, and then call the Plan
's onRender
callback of the shim component, which triggers this rendering function.
This contains the widget specific rendering instructions.
render :: WindowT (Design Model Plan) ReactMl ()
This a a monad transformer stack over Identity
. This ensures only pure effects are allowed.
gadget
This contains the state update logic:
gadget :: G.Gadget () Action (SuperModel Model Plan) (DList Command)
This a a monad transformer stack over Identity
. This ensures only pure effects are allowed.
When required, STM
can always be hoist (hoist generalize)
into the gadget using Control.Monad.Morph
.