MFlow-0.4.2: stateful, RESTful web framework

Safe HaskellNone

MFlow

Contents

Description

Non monadic low level primitives that implement the MFlow application server. See MFlow.Form for the higher level interface that you may use.

it implements an scheduler of 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 will send additional messages to the source and wait for the responses. The diaglog is identified by a Token, which is associated to the flow. . The computation state is optionally logged. On timeout, the process is killed. When invoked again, the execution state is recovered as if no interruption took place.

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 and applicative combinator as well as an higher comunication interface.

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

MFlow.Forms.Blaze.Html is an instantaiation for blaze-html

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

There are some *.All packages that contain a mix of these instantiations. For exmaple, MFlow.Wai.Blaze.Html.All includes most of all necessary for using MFlow with Wai http://hackage.haskell.org/package/wai and Blaze-html http://hackage.haskell.org/package/blaze-html

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 are provided only at this level.

stateless and transient server processeses are also possible. the first are request-response . transient processes do not persist after timeout, so they restart anew after a timeout or a crash.

Synopsis

Documentation

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
 
tpath :: [String]
 
tenv :: Params
 
tsendq :: MVar Req
 
trecq :: 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 :: Token -> HttpData -> IO ()Source

send a complete response send :: Token -> HttpData -> IO()

sendFragment :: Token -> HttpData -> IO ()Source

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

sendEndFragment :: Token -> HttpData -> IO ()Source

Deprecated: use send to end a fragmented response instead

sendToMF :: (Typeable a, Processable a) => Token -> a -> IO ()Source

Flow configuration

setNoScript :: [Char] -> IO ()Source

set the flow to be executed when the URL has no path. The home page.

By default it is noscript. Although it is changed by runNavigation to his own flow name.

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 (WorkflowList IO Token ())Source

return the list of the scheduler

transient :: (Token -> IO ()) -> FlowSource

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 :: (Params -> IO HttpData) -> FlowSource

executes a simple request-response computation that receive the params and return a response

It is used with addMessageFlows

There is a higuer level version wstateless in MFLow.Forms

anonymous :: [Char]Source

The anonymous user

hlog :: HandleSource

The handler of the error log

setNotFoundResponse :: (Bool -> String -> ByteString) -> IO ()Source

set the 404 not found response.

The parameter is as follows: (Bool Either if the user is Administrator or not -> String The error string -> HttpData) The response. See defNotFoundResponse code for an example

ByteString tags

very basic but efficient bytestring 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

user

setAdminUser :: MonadIO m => UserStr -> PasswdStr -> m ()Source

set the Administrator user and password. It must be defined in Main , before any configuration parameter is read, before the execution of any flow

data Auth Source

Constructors

Auth 

setAuthMethod :: Auth -> IO ()Source

set an authentication method

static files

config

data Config Source

Constructors

Config 

Fields

cadmin :: UserStr

Administrator name

cjqueryScript :: String

URL of jquery

cjqueryCSS :: String

URL of jqueryCSS

cjqueryUI :: String

URL of jqueryUI

cnicEditUrl :: String

URL of the nicEdit editor

setFilesPath :: MonadIO m => String -> m ()Source

Set the path of the files in the web server. The links to the files are relative to it. The files are cached (memoized) according with the Data.TCache policies in the program space. This avoid the blocking of the efficient GHC threads by frequent IO calls.So it enhances the performance in the context of heavy concurrence. It uses Memoization. The caching-uncaching follows the setPersist criteria

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, then wait for the response and return it.

It is the core of the application server. MFLow.Wai and MFlow.Hack use it