jmacro-rpc-0.3.2: JSON-RPC clients and servers using JMacro, and evented client-server Reactive Programming.

Copyright(c) Gershom Bazerman, 2012
LicenseBSD 3 Clause
Maintainergershomb@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Network.JMacroRPC.Panels

Contents

Description

The Panels library provides continuation-style compositional web development with no scaling hassle. On the server side, Panels are entirely stateless, storing no client-specific state. This also means that requests can be sharded to multiple servers without worrying about replication of large session objects (authentication choices are another issue entirely).

Code is written with a set of combinators over Panels, which package up display and behavior simultaneously. Panels, inspired by FRP, can provide Signals, which are sampleable, Events, which are discrete and can trigger updates, and Sinks which can be bound to Signals (behaving similarly to FRP wormholes). Semantics, by virtue of client-server interaction, are necessarily evented rather than continuous.

Panels, which are built using this library, can then be displayed using one of a number of servers as backends. New backends can be created with the panelToPageGen function.

Example usage:

testPanel :: (Monad m, Functor m) => Panel m
testPanel =    para "This is an example"
          <> plainHTML Blaze.br
          <> inDiv [
                  select ("default",1::Int) [("another",2)] $ \ evt selSignal selPanel ->
                  selPanel <>
                   (onEvent evt $
                    withSample selSignal $ \ selChoice ->
                    select (show selChoice, selChoice)
                        [(show $ selChoice + 1, selChoice + 1)] $ \ _evt selSignal2 selPanel2 ->
                    button "click me" $ \ buttonEvt buttonPanel ->
                    onEvent buttonEvt $
                    withSample selSignal2 $ \ selChoice2 ->
                    (selPanel2 <> buttonPanel <> plainHTML Blaze.br
                     <> (para $ "you chose: " ++ show (selChoice, selChoice2))))
             ]

The above code displays two dropdown menus and a button. The first dropdown determines the contents of the second. On clicking the button, the text updates with choices from both the first and second dropdowns.

See the source of calcPanel for an example of mixed client/server updates with more complicated stateful interaction.

Synopsis

Base Types

data JS Source

Type tag for Sinks and Signals that can be run in pure JavaScript.

data Hask Source

Type tag for Sinks and Signals that require server-side interaction.

type PanelPath = [Int] Source

Unique label for any given panel in a control structure.

data Event Source

Conceptually, an Event is something that can trigger an update. We can join two events (which gives us "or" semantics), and we can trigger on an event. That's it. In reality, an event is composed of the panelpaths to it's sources.

Constructors

Event [PanelPath] 

Instances

data Signal typ a where Source

A Signal can contain information drawn from client-side inputs. Signals are tagged as JS, Hask, or parametric. A signal of type JS can be read from purely on the client side, with no round trip. A signal of type Hask forms an applicative functor, so we can build server-side values with complex computed behaviours. Note that Signal Hask actually bends the applicative functor laws in that fmap id on a signal that can be calculated directly in JS can send it to a signal that cannot be. This is a flaw, and it will be fixed.

Constructors

PureSig :: a -> Signal typ a 
OneSig :: FromJSON a => PanelPath -> Signal typ a 
MultiSig :: Signal typ1 a -> Signal typ2 b -> ((a, b) -> c) -> Signal Hask c 

data Sink typ m a where Source

Sinks likewise are tagged as JS, Hask, or parametric. A sink of type JS can be written to purely on the client side, with no round trip. A sink of type Hask is a contravariant functor.

Constructors

ServerSink :: (a -> PState m [JStat]) -> Sink Hask m a 
PureSink :: ToJExpr a => JExpr -> Sink typ m a 

Instances

The PState Monad Transformer

data PanelState Source

A PanelState contains environment information used to render Panels.

Instances

type PState m a = StateT PanelState m a Source

The PState Monad Transformer provides access o the PanelState.

newIdent :: (Monad m, Functor m) => PState m PanelPath Source

We can get a fresh identifier out of a panel state.

descended :: (Monad m, Functor m) => (PanelPath -> PState m a) -> PState m a Source

And we can get an identifier out before descending into a "local" environment whose identifiers don't affect the main supply. Hence if a local environment alters its pattern of consumption, identifiers in the outer environment will remain stable.

Page Slices and Panels

data PageSlice Source

A PageSlice is a pair of Html and JavaScript. When a Panel is rendered, all JavaScript ends up joined together in the head of the page, and all HTML below it. PageSlices are naturally Monoidal, just as Html is.

Constructors

PS 

Fields

htmlP :: Html
 
jsP :: [JStat]
 

Instances

data Panel m Source

A Panel is the pair of an action to produce a PageSlice and an action to produce a list of locations with updated PageSlices. The former is used to draw the initial page, and the latter to modify it in response to events. Panels are also naturally Monoidal.

Constructors

Panel 

Instances

Monad m => Monoid (Panel m) 

Base Type Combinators

pureSig :: a -> Signal typ a Source

Since only some Signals are applicative functors, pureSig provides a pure operation over all Signals.

zipSinks :: Monad m => Sink Hask m a -> Sink Hask m b -> Sink Hask m (a, b) Source

We can zip sinks up to combine them.

contramapJs :: ToJExpr a => JExpr -> Sink JS m b -> Sink JS m a Source

A JavaScript funcion can be contravariantly mapped over a Sink JS

Building Panels

plainHTML :: (Monad m, Functor m) => Html -> Panel m Source

We can lift any Html into a Panel trivially.

onHtml :: (Monad m, Functor m) => (Html -> Html) -> Panel m -> Panel m Source

Similarly, we can map over any Html inside a panel (although the behavior may be odd on panels with internal update semantics).

joinWith :: (Monad m, Functor m) => ([Html] -> Html) -> [Panel m] -> Panel m Source

Given a function to join Html sections, we can fuse a list of panels into a single pannel by lifting that function.

buildInput Source

Arguments

:: (FromJSON a, ToJSON a, Monad m, Functor m) 
=> (PanelPath -> (a, sinks, Panel m))

given a path, construct a so-located panel with an intial value and possibly some Sinks.

-> (Event -> Signal typ a -> sinks -> Panel m -> Panel m)

given a so-constructed panel, event, and signal, declare what panel to produce.

-> Panel m

result panel

This is a general purpose function for constructing Panels that provide signals and events, and optionally sinks. It takes a function from an identifier path to an intial value of a signal, optional sinks into the signal, and a panel "controlling" the signal. From this it yields a continuation function from the event and signal associated wih the panel, the optional sinks, and the signal "control" panel to a new panel to the new panel iself. Usage of this function is best understood by viewing the source of inputs built using it.

inDiv :: (Monad m, Functor m) => [Panel m] -> Panel m Source

Put a bunch of panels into a single div element. inDiv = onHtml H.div . mconcat

para :: (Monad m, Functor m) => String -> Panel m Source

Put some text into a p element. para = plainHTML . H.p . fromString

mkTable :: (Monad m, Functor m) => Int -> [Panel m] -> Panel m Source

Align a list of panels into a table with rows of the specified width. mkTable n xs = onHtml H.table . mconcat . map row $ chunksOf n xs where row ys = onHtml H.tr . mconcat $ map (onHtml H.td) ys

Interacting with signals, sinks, and events

withSample :: (FromJSON a, Monad m, Functor m) => Signal typ a -> (a -> Panel m) -> Panel m Source

Given an arbitrary Signal, and a continuation accepting a value of the underlying type of the signal, yield a simple Panel.

sampleSigJs :: ToJSON a => Signal JS a -> JExpr Source

Given a Signal JS, produce a JavaScript expression that samples the value of the signal.

onEvent :: (Monad m, Functor m) => Event -> Panel m -> Panel m Source

Given an Event, and a Panel, update the Panel each time the event fires.

tellSink :: (Functor m, Monad m) => Sink typ m a -> a -> Panel m Source

Feed a value to a Sink.

bindSigSink :: (Monad m, Functor m, FromJSON a, ToJSON a) => Event -> Signal typ1 a -> Sink typ2 m a -> Panel m Source

Given an event, a signal, and a sink, on each firing of the event, feed the sink the current sampled value of the signal. If the Signal and Sink are both in JS, this can happen entirely on the client side.

sampleIO :: Monad m => m a -> (a -> Panel m) -> Panel m Source

Perform an action in the underlying monad and feed the result to a panel. Synchronous. Note that this action will occur on every update, even when guarded by an onEvent.

bindEventIO :: (Monad m, Functor m) => Event -> m () -> Panel m Source

Execute an IO action when triggered by an event. This action only occurs when the event fires. bindEventIO e act = onEvent e $ Panel (return mempty) (lift act >> return mempty)

Derived panels and inputs.

button :: (Monad m, Functor m) => String -> (Event -> Panel m -> Panel m) -> Panel m Source

Takes an initial value and a continuation taking an event and the button itself, yields a panel.

select :: (Monad m, Functor m, ToJSON a, FromJSON a) => (String, a) -> [(String, a)] -> (Event -> Signal typ a -> Panel m -> Panel m) -> Panel m Source

Takes an intial (label, value) pair, a list of pairs of labeled values, and a continuation, building a Panel with a dropdown selector.

selectInput :: (Monad m, Functor m, FromJSON a, ToJSON a) => (String, a) -> [(String, a)] -> (Event -> a -> Panel m -> Panel m) -> Panel m Source

a wrapper around select that immediately samples from the yielded signal. selectInput defOpt opts k = select defOpt opts $ e sig p -> withSample sig $ i -> k e i p

textPane :: (Monad m, Functor m) => String -> (Event -> Signal typ String -> Sink typ m String -> Panel m -> Panel m) -> Panel m Source

A basic text input box. This box provides a Sink as well as a Signal, so it's contents can be controlled from elsewhere in the Panel.

newVar :: (Monad m, Functor m, ToJSON a, FromJSON a, ToJExpr a) => a -> (Event -> Signal typ a -> Sink typ m a -> Panel m -> Panel m) -> Panel m Source

A hidden input Panel that can be used as a mutable store, akin to an IORef or MVar.

Running Panels

panelPrelude :: JStat Source

JavaScript code for the reactive runtime system.

panelToPageGen Source

Arguments

:: (Monad m, Functor m, ToJsonRPC (m (Either String UpdateList)) m) 
=> ([JsonRPC m ()] -> m resp)

A function which serves stateless JsonRPCs.

-> (Text -> m resp)

A function which renders Text to a server response.

-> Maybe String

An optional url to find JQuery

-> String

A page title.

-> Panel m

The panel to server

-> (m resp, m resp)

Two page handlers -- one for handling updates (POSTs), and the second for rendering the initial page (GETs).

General function used to create backends for different servers and frameworks.

Examples

calcPanel :: (Monad m, Functor m) => Panel m Source

Example panel that displays a calculator.