MFlow-0.1.5.2: Web app server for stateful processes with safe, composable user interfaces.

Safe HaskellNone

MFlow

Contents

Description

Non monadic low level support stuff for the MFlow application server. (See MFlow.Form for the higher level interfaces) it implements an scheduler of queued Processable messages that are served according with the source identification and the verb invoked. The scheduler executed the appropriate workflow (using the workflow package). The workflow may send additional messages to the source, identified by a Token . The computation state is optionally logged and recovered.

The message communication is trough polimorphic, monoidal queues. There is no asumption about message codification, so instantiations of this scheduler for different infrastructures is possible, including non-Web based ones as long as they support or emulate cookies.

MFlow.Hack is an instantiation for the Hack interface in a Web context.

MFlow.Wai is a instantiation for the WAI interface.

MFlow.Forms implements a monadic type safe interface with composabe widgets and a higher comunication interface.

MFlow.Forms.XHtml is an instantiation for the Text.XHtml format

MFlow.Forms.HSP is an instantiation for the Haskell Server Pages format

In order to manage resources, there are primitives that kill the process and its state after a timeout.

All these details are hidden in the monad of MFlow.Forms that provides an higher level interface.

Fragment based streaming sendFragment sendEndFragment are provided only at this level.

stateless and transient server processeses are also possible. stateless are request-response with no intermediate messaging dialog. transient processes have no persistent state, so they restart anew after a timeout or a crash.

Synopsis

Documentation

type Workflow m = WF Stat m

data Token Source

a Token identifies a flow that handle messages. The scheduler compose a Token with every Processable message that arrives and send the mesage to the appropriate flow.

Constructors

Token 

Fields

twfname :: String
 
tuser :: String
 
tind :: String
 
q :: MVar Req
 
qr :: MVar Resp
 

type ProcList = WorkflowList IO Token ()Source

List of (wfname, workflow) pairs, to be scheduled depending on the message's pwfname

low level comunication primitives. Use ask instead

send :: ToHttpData a => Token -> a -> IO ()Source

send a complete response

sendFlush :: ToHttpData a => Token -> a -> IO ()Source

sendFragment :: ToHttpData a => Token -> a -> IO ()Source

send a response fragment. Useful for streaming. the last packet must sent trough send

Flow configuration

addMessageFlows :: [([Char], Token -> Workflow IO ())] -> IO ()Source

add a list of flows to be scheduled. Each entry in the list is a pair (path, flow)

getMessageFlows :: IO (Map String (Token -> Workflow IO ()))Source

return the list of the scheduler

transient :: (Token -> IO ()) -> Token -> Workflow IO ()Source

Executes a monadic computation that send and receive messages, but does not store its state in permanent storage. The process once stopped, will restart anew

stateless :: ToHttpData b => (Params -> IO b) -> Token -> Workflow IO ()Source

executes a simple monadic computation that receive the params and return a response

It is used with addMessageFlows hackMessageFlow or waiMessageFlow

anonymous :: [Char]Source

The anonymous user

noScript :: [Char]Source

It is the path of the root flow

hlog :: HandleSource

The handler of the error log

setNotFoundResponse :: MonadIO m => (ByteString -> ByteString) -> m ()Source

set the 404 not found response

ByteString tags

very basic but efficient tag formatting

btag :: String -> Attribs -> ByteString -> ByteStringSource

Writes a XML tag in a ByteString. It is the most basic form of formatting. For more sophisticated formatting , use MFlow.Forms.XHtml or MFlow.Forms.HSP.

bhtml :: Attribs -> ByteString -> ByteStringSource

 bhtml ats v= btag "html" ats v

bbody :: Attribs -> ByteString -> ByteStringSource

 bbody ats v= btag "body" ats v

internal use

msgScheduler :: (Typeable a, Processable a) => a -> IO (HttpData, ThreadId)Source

The scheduler creates a Token with every Processable message that arrives and send the mesage to the appropriate flow, get the response and return it.