| Stability | experimental |
|---|---|
| Maintainer | gershomb@gmail.com |
| Safe Haskell | None |
Network.JMacroRPC.Snap
Description
Snap backend for JMacro-RPC.
Example usage:
module Main where
import Network.JMacroRPC.Snap
import Snap.Http.Server
import Snap.Core
import Language.Javascript.JMacro
import Control.Concurrent
import Control.Monad.Trans
import Network.JMacroRPC.Base
import Text.XHtml hiding(dir)
import qualified Data.Text as T
jsScript f = script (primHtml f) ! [thetype "text/javascript"]
jsScript' = jsScript . show . renderJs
testPage = mkConversationPageNoCulling pageFun (newMVar (1::Int)) jRpcs
where pageFun :: JStat -> Snap ()
pageFun js = writeText $ T.pack $ show $
(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 -> (liftIO $ retRight =<< modifyMVar s (\i -> return (i+1,i)) :: Snap (Either String Int))
retRight :: a -> IO (Either String a)
retRight = return . Right
main = quickHttpServe =<< testPage
Every invocation of this page (including from the same browser) will have a distinct, stateful, counter, stored server-side.
- serveRpcs :: MonadSnap m => (Int -> m s) -> [JsonRPC m s] -> m ()
- mkConversationPage :: MonadSnap m => IO timestamp -> (IntMap (timestamp, s) -> IO (IntMap (timestamp, s))) -> (JStat -> m ()) -> IO s -> [JsonRPC m s] -> IO (m ())
- mkConversationPageNoCulling :: MonadSnap m => (JStat -> m ()) -> IO s -> [JsonRPC m s] -> IO (m ())
- panelToPage :: Maybe String -> String -> Panel Snap -> Snap ()
Documentation
Arguments
| :: MonadSnap m | |
| => IO timestamp | Get an abstract timestamp |
| -> (IntMap (timestamp, s) -> IO (IntMap (timestamp, s))) | Cull a map of conversations based on a timestamp |
| -> (JStat -> m ()) | 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 m s] | JSON RPCs to serve and make available to clientside javascript |
| -> IO (m ()) |
This general handler allows explicit culling of conversation state.