jmacro-rpc-happstack-0.2: Happstack backend for jmacro-rpc

Stabilityexperimental
Maintainergershomb@gmail.com
Safe HaskellNone

Network.JMacroRPC.Happstack

Description

Happstack backend for JMacro-RPC.

Example usage:

 
 module Main where
 import Network.JMacroRPC.Happstack
 import Happstack.Server
 import Language.Javascript.JMacro
 import Control.Concurrent
 import Network.JMacroRPC.Base
 import Text.XHtml hiding(dir)

 jsScript f = script (primHtml f) ! [thetype "text/javascript"]
 jsScript' = jsScript . show . renderJs

 testPage :: IO (ServerPartT IO Response)
 testPage = mkConversationPageNoCulling pageFun (newMVar (1::Int)) jRpcs
     where pageFun js = return $ toResponse $
                        (header << [script ! [src "https://ajax.googleapis.com/ajax/libs/jquery/1.6.2/jquery.min.js"] << noHtml]) +++
                        jsScript' js +++
                        jsScript' ([jmacro|$(\
                                      {
                                            var b = $("<button>click me!</button>");
                                            $("body").append(b);
                                            b.click(\ {
                                                var c = getCounter();
                                                alert ("counter is: " + c);
                                            });
                                      });
                                   |]);
           jRpcs = [getCounterRPC]
           getCounterRPC =
               toJsonConvRPC "getCounter" $ \s -> retRight =<< modifyMVar s (\i -> return (i+1,i))

 retRight :: a -> IO (Either String a)
 retRight = return . Right

 main = simpleHTTP nullConf =<< testPage

Every invocation of this page (including from the same browser) will have a distinct, stateful, counter, stored server-side.

Synopsis

Documentation

mkConversationPageSource

Arguments

:: forall m s timestamp . (Monad m, Functor m, MonadIO m) 
=> IO timestamp

Get an abstract timestamp

-> (IntMap (timestamp, s) -> IO (IntMap (timestamp, s)))

Cull a map of conversations based on a timestamp

-> (JStat -> ServerPartT m Response)

Take some JMacro Javascript and splice it into some generated page.

-> IO s

Generate an empty initial state for a conversation. States are responsible for using their own MVars or the like to allow sharing.

-> [JsonRPC (ServerPartT m) s]

JSON RPCs to serve and make available to clientside javascript

-> IO (ServerPartT m Response) 

This general handler allows explicit culling of conversation state.

mkConversationPageNoCulling :: forall m s. (Monad m, Functor m, MonadIO m) => (JStat -> ServerPartT m Response) -> IO s -> [JsonRPC (ServerPartT m) s] -> IO (ServerPartT m Response)Source

This simple handler allows conversation state to grow without bounds.

panelToPage :: (Monad m, Functor m, MonadIO m) => String -> Panel (ServerPartT m) -> ServerPartT m ResponseSource

Render a Panel as a ServerPartT m Response.