MFlow-0.4.6.0: stateful, RESTful web framework

Safe HaskellNone
LanguageHaskell98

MFlow.Forms

Contents

Description

MFlow run stateful server processes. This version is the first stateful web framework that is as RESTful as a web framework can be.

The routes are expressed as normal, monadic Haskell code in the FlowM monad. Local links point to alternative routes within this monadic computation just like a textual menu in a console application. Any GET page is directly reachable by means of a RESTful URL.

At any moment the flow can respond to the back button or to any RESTful path that the user may paste in the navigation bar. If the procedure is waiting for another different page, the FlowM monad backtrack until the path partially match . From this position the execution goes forward until the rest of the path match. This way the statelessness is optional. However, it is possible to store a session state, which may backtrack or not when the navigation goes back and forth. It is up to the programmer.

All the flow of requests and responses are coded by the programmer in a single procedure. Although single request-response flows are possible. Therefore, the code is more understandable. It is not continuation based. It uses a log for thread state persistence and backtracking for handling the back button. Back button state synchronization is supported out-of-the-box

The MFlow architecture is scalable, since the state is serializable and small

The processes are stopped and restarted by the application server on demand, including the execution state (if the Workflow monad is used). Therefore session management is automatic. State consistence and transactions are given by the TCache package.

The processes interact trough widgets, that are an extension of formlets with additional applicative combinators, formatting, link management, callbacks, modifiers, caching, ByteString conversion and AJAX. All is coded in pure Haskell.

The interfaces and communications are abstract, but there are bindings for blaze-html, HSP, Text.XHtml and ByteString , Hack and WAI but it can be extended to non Web based architectures.

Bindings for hack, and HSP >= 0.8, are not compiled by Hackage, and do not appear, but are included in the package files. To use them, add then to the exported modules and execute cabal install

It is designed for applications that can be run with no deployment with runghc in order to speed up the development process. see http://haskell-web.blogspot.com.es/2013/05/a-web-application-in-tweet.html

This module implement stateful processes (flows) that are optionally persistent. This means that they automatically store and recover his execution state. They are executed by the MFlow app server. defined in the MFlow module.

These processes interact with the user trough user interfaces made of widgets (see below) that return back statically typed responses to the calling process. Because flows are stateful, not request-response, the code is more understandable, because all the flow of request and responses is coded by the programmer in a single procedure in the FlowM monad. Although single request-response flows and callbacks are possible.

This module is abstract with respect to the formatting (here referred with the type variable view) . For an instantiation for Text.XHtml import MFlow.Forms.XHtml, MFlow.Hack.XHtml.All or MFlow.Wai.XHtml.All . To use Haskell Server Pages import MFlow.Forms.HSP. However the functions are documented here.

ask is the only method for user interaction. It run in the MFlow view m monad, with m the monad chosen by the user, usually IO. It send user interfaces (in the View view m monad) and return statically typed responses. The user interface definitions are based on a extension of formlets (http://www.haskell.org/haskellwiki/Formlets) with the addition of caching, links, formatting, attributes, extra combinators, callbacks and modifiers. The interaction with the user is stateful. In the same computation there may be many request-response interactions, in the same way than in the case of a console applications.

  • APPLICATION SERVER

Therefore, session and state management is simple and transparent: it is in the Haskell structures in the scope of the computation. transient (normal) procedures have no persistent session state and stateless procedures accept a single request and return a single response.

step is a lifting monad transformer that permit persistent server procedures that remember the execution state even after system shutdowns by using the package workflow (http://hackage.haskell.org/package/Workflow) internally. This state management is transparent. There is no programmer interface for session management.

The programmer set the process timeout and the session timeout with setTimeouts. If the procedure has been stopped due to the process timeout or due to a system shutdown, the procedure restart in the last state when a request for this procedure arrives (if the procedure uses the step monad transformer)

  • WIDGETS

The correctness of the web responses is assured by the use of formLets. But unlike formLets in its current form, it permits the definition of widgets. A widget is a combination of formLets and links within its own formatting template, all in the same definition in the same source file, in plain declarative Haskell style.

The formatting is abstract. It has to implement the FormInput class. There are instances for Text.XHtml (MFlow.Forms.XHtml), Haskell Server Pages (MFlow.Forms.HSP) and ByteString. So widgets can use any formatting that is instance of FormInput. It is possible to use more than one format in the same widget.

Links defined with wlink are treated the same way than forms. They are type safe and return values to the same flow of execution. It is possible to combine links and forms in the same widget by using applicative combinators but also additional applicative combinators like <+> !*> , |*|. Widgets are also monoids, so they can be combined as such.

  • NEW IN THIS RELEASE
Runtime templates
template, edTemplate, witerate and dField permit the edition of the widget content at runtime, and the management of placeholders with input fields and data fields within the template with no navigation in the client, little bandwidth usage and little server load. Even less than using autoRefresh.
  • IN PREVIOUS RELEASES

{AutoRefresh] Using autoRefresh, Dynamic widgets can refresh themselves with new information without forcing a refresh of the whole page

Push
With push a widget can push new content to the browser when something in the server happens
Error traces
using the monadloc package, now each runtime error (in a monadic statement) has a complete execution trace.
RESTful URLs
Now each page is directly reachable by means of a intuitive, RESTful URL, whose path is composed by the succession of links clicked to reach such page and such point in the procedure. Just what you would expect.
Page flows
each widget-formlet can have its own independent behavior within the page. They can refresh independently trough AJAX by means of autoRefresh. Additionally, pageFlow initiates the page flow mode or a subpage flow by adding a well know identifier prefix for links and form parameters.
Modal Dialogs
wdialog present a widget within a modal or non modal jQuery dialog. while a monadic widget-formlet can add different form elements depending on the user responses, wcallback can substitute the widget by other. (See 'Demos/demos.blaze.hs' for some examples)
JQuery widgets
with MFlow interface: getSpinner, datePicker, wdialog
WAI interface
Now MFlow works with Snap and other WAI developments. Include MFlow.Wai or MFlow.Wai.Blaze.Html.All to use it.
blaze-html support
see http://hackage.haskell.org/package/blaze-html import MFlow.Forms.Blaze.Html or MFlow.Wai.Blaze.Html.All to use Blaze-Html
AJAX
Now an Ajax procedures (defined with ajax can perform many interactions with the browser widgets, instead of a single request-response (see ajaxSend).
Active widgets
MFlow.Forms.Widgets contains active widgets that interact with the server via Ajax and dynamically control other widgets: wEditList, autocomplete autocompleteEdit and others.
Requirements
a widget can specify JavaScript files, JavaScript online scripts, CSS files, online CSS and server processes and any other instance of the Requirement class. See requires and WebRequirements
content-management
for templating and online edition of the content template. See tFieldEd tFieldGen and tField
multilanguage
see mField and mFieldEd
URLs to internal states
if the web navigation is trough GET forms or links, an URL can express a direct path to the nth step of a flow, So this URL can be shared with other users. Just like in the case of an ordinary stateless application.
Back Button
This is probably the first implementation in any language where the navigation can be expressed procedurally and still it works well with the back button, thanks to monad magic. (See http://haskell-web.blogspot.com.es/2012/03//failback-monad.html)
Cached widgets
with cachedWidget it is possible to cache the rendering of a widget as a ByteString (maintaining type safety) , the caching can be permanent or for a certain time. this is very useful for complex widgets that present information. Specially if the widget content comes from a database and it is shared by all users.
Callbacks
waction add a callback to a widget. It is executed when its input is validated. The callback may initiate a flow of interactions with the user or simply executes an internal computation. Callbacks are necessary for the creation of abstract container widgets that may not know the behavior of its content. with callbacks, the widget manages its content as black boxes.
Modifiers
wmodify change the visualization and result returned by the widget. For example it may hide a login form and substitute it by the username if already logged.

Example:

 ask $ wform userloginform `validate` valdateProc `waction` loginProc `wmodify` hideIfLogged
attributes for formLet elements
to add attributes to widgets. See the <! operator
ByteString normalization and heterogeneous formatting
For caching the rendering of widgets at the ByteString level, and to permit many formatting styles in the same page, there are operators that combine different formats which are converted to ByteStrings. For example the header and footer may be coded in XML, while the formlets may be formatted using Text.XHtml.
File Server
With file caching. See "MFlow.File Server"

Synopsis

Basic definitions

data FlowM v m a Source

the FlowM monad executes the page navigation. It perform Backtracking when necessary to synchronize when the user press the back button or when the user enter an arbitrary URL. The instruction pointer is moved to the right position within the procedure to handle the request.

However this is transparent to the programmer, who codify in the style of a console application.

Instances

MonadTrans (FlowM view) 
Monad m => MonadState (MFlowState v) (FlowM v m) 
(Monad m, Functor m) => Alternative (FlowM v m) 
Monad m => Monad (FlowM v m) 
(Monad m, Functor m) => Functor (FlowM v m) 
(Monad m, Functor m) => Applicative (FlowM v m) 
MonadLoc (FlowM v IO) 
MonadIO m => MonadIO (FlowM v m) 

newtype View v m a Source

View v m a is a widget (formlet) with formatting v running the monad m (usually IO) and which return a value of type a

It has Applicative, Alternative and Monad instances.

Things to know about these instances:

If the View expression does not validate, ask will present the page again.

Alternative instance: Both alternatives are executed. The rest is as usual

Monad Instance:

The rendering of each statement is added to the previous. If you want to avoid this, use wcallback

The execution is stopped when the statement has a formlet-widget that does not validate and return an invalid response (So it will present the page again if no other widget in the expression validates).

The monadic code is executed from the beginning each time the page is presented or refreshed

use pageFlow if your page has more than one monadic computation with dynamic behavior

use pageFlow to identify each subflow branch of a conditional

For example:

pageFlow "myid" $ do
     r <- formlet1
     liftIO $ ioaction1 r
     s <- formlet2
     liftIO $ ioaction2 s
     case s of
      True  -> pageFlow "idtrue" $ do ....
      False -> paeFlow "idfalse" $ do ...
     ...

Here if formlet2 do not validate, ioaction2 is not executed. But if formLet1 validates and the page is refreshed two times (because formlet2 has failed, see above),then ioaction1 is executed two times. use cachedByKey if you want to avoid repeated IO executions.

Constructors

View 

Fields

runView :: WState v m (FormElm v a)
 

Instances

Monoid view => MonadTrans (View view) 
(FormInput view, Monad m) => MonadState (MFlowState view) (View view m) 
(FormInput view, Functor m, Monad m) => Alternative (View view m) 
(FormInput view, Monad m) => Monad (View view m) 
(Monad m, Functor m) => Functor (View view m) 
(Monoid view, Functor m, Monad m) => Applicative (View view m) 
FormInput v => MonadLoc (View v IO) 
(FormInput view, MonadIO m) => MonadIO (View view m) 
(FormInput v, Monad m, Functor m, Monoid a) => Monoid (View v m a) 

data FormElm view a Source

Constructors

FormElm view (Maybe a) 

Instances

Functor (FormElm view) 
(Monoid view, Serialize a) => Serialize (FormElm view a) 
Typeable (* -> * -> *) FormElm 

class (Monoid view, Typeable view) => FormInput view where Source

Minimal interface for defining the basic form and link elements. The core of MFlow is agnostic about the rendering package used. Every formatting (either HTML or not) used with MFlow must have an instance of this class. See "MFlow.Forms.Blaze.Html for the instance for blaze-html" MFlow.Forms.XHtml for the instance for Text.XHtml and MFlow.Forms.HSP for the instance for Haskell Server Pages.

Methods

toByteString :: view -> ByteString Source

toHttpData :: view -> HttpData Source

fromStr :: String -> view Source

fromStrNoEncode :: String -> view Source

ftag :: String -> view -> view Source

inred :: view -> view Source

flink :: String -> view -> view Source

flink1 :: String -> view Source

finput :: Name -> Type -> Value -> Checked -> OnClick -> view Source

ftextarea :: String -> Text -> view Source

fselect :: String -> view -> view Source

foption :: String -> view -> Bool -> view Source

foption1 :: String -> Bool -> view Source

formAction :: String -> String -> view -> view Source

attrs :: view -> Attribs -> view Source

Users

data Auth Source

Constructors

Auth 

userRegister :: MonadIO m => UserStr -> PasswdStr -> m (Maybe String) Source

Register a user with the auth method.

setAuthMethod :: Auth -> IO () Source

Sets an authentication method, that includes the registration and validation calls. Both return Nothing if successful. Otherwise they return a text message explaining the failure.

userValidate :: (FormInput view, MonadIO m) => (UserStr, PasswdStr) -> m (Maybe view) Source

Authentication against userRegistered users. to be used with validate

isLogged :: MonadState (MFlowState v) m => m Bool Source

If the user is logged or is anonymous

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 and before the execution of any flow.

getUserSimple :: (FormInput view, Typeable view) => FlowM view IO String Source

If not logged, perform login. otherwise return the user

getUserSimple= getUser Nothing userFormLine

getUser :: (FormInput view, Typeable view) => Maybe String -> View view IO (Maybe (UserStr, PasswdStr), Maybe String) -> FlowM view IO String Source

Very basic user authentication. The user is stored in a cookie. it looks for the cookie. If no cookie, it ask to the user for a userRegistered user-password combination. The user-password combination is only asked if the user has not logged already otherwise, the stored username is returned.

getUser mu form= ask $ userWidget mu form

userFormLine :: (FormInput view, Functor m, Monad m) => View view m (Maybe (UserStr, PasswdStr), Maybe PasswdStr) Source

Is an example of login/register validation form needed by userWidget. In this case the form field appears in a single line. it shows, in sequence, entries for the username, password, a button for logging, a entry to repeat password necessary for registering and a button for registering. The user can build its own user login/validation forms by modifying this example

 userFormLine=
     (User <$> getString (Just "enter user") <*> getPassword <+> submitButton "login")
     <+> fromStr "  password again" +> getPassword <* submitButton "register"

userLogin :: (FormInput view, Functor m, Monad m) => View view m (Maybe (UserStr, PasswdStr), Maybe String) Source

Example of user/password form (no validation) to be used with userWidget

logout :: (MonadState (MFlowState view) m, MonadIO m) => m () Source

userWidget :: (MonadIO m, Functor m, FormInput view) => Maybe String -> View view m (Maybe (UserStr, PasswdStr), Maybe String) -> View view m String Source

It creates a widget for user login/registering. If a user name is specified in the first parameter, it is forced to login/password as this specific user. If this user was already logged, the widget return the user without asking. If the user press the register button, the new user-password is registered and the user logged.

paranoidUserWidget :: (FormInput view, MonadIO m, Functor m) => Maybe String -> View view m (Maybe (UserStr, PasswdStr), Maybe [Char]) -> View view m String Source

Uses 4 different keys to encrypt the 4 parts of a MFlow cookie.

encryptedUserWidget :: (FormInput view, MonadIO m, Functor m) => Maybe String -> View view m (Maybe (UserStr, PasswdStr), Maybe [Char]) -> View view m String Source

Uses a single key to encrypt the MFlow cookie.

login :: (MonadState (MFlowState view) m, MonadIO m) => String -> m () Source

change the user

It is supposed that the user has been validated

User interaction

ask :: FormInput view => View view IO a -> FlowM view IO a Source

page :: FormInput view => View view IO a -> FlowM view IO a Source

A synonym of ask.

Maybe more appropriate for pages with long interactions with the user while the result has little importance.

askt :: FormInput v => (Int -> a) -> View v IO a -> FlowM v IO a Source

for compatibility with the same procedure in askt. This is the non testing version

askt v w= ask w

hide one or the other

clearEnv :: MonadState (MFlowState view) m => m () Source

Clears the environment

clearEnv' :: MonadState (MFlowState view) m => m () Source

clear the request paramters and the rest path.

wstateless :: (Typeable view, FormInput view) => View view IO () -> Flow Source

Creates a stateless flow (see stateless) whose behavior is defined as a widget. It is a higher level form of the latter

pageFlow :: (Monad m, Functor m, FormInput view) => String -> View view m a -> View view m a Source

Prepares the state for a page flow. It add a prefix to every form element or link identifier for the formlets and also keep the state of the links clicked and form input entered within the widget. If the computation within the widget has branches if case etc, each branch must have its pageFlow with a distinct identifier. See http://haskell-web.blogspot.com.es/2013/06/the-promising-land-of-monadic-formlets.html

formLets

They usually produce the HTML form elements (depending on the FormInput instance used) It is possible to modify their attributes with the <! operator. They are combined with applicative combinators and some additional ones formatting can be added with the formatting combinators. modifiers change their presentation and behavior

getString :: (FormInput view, Monad m) => Maybe String -> View view m String Source

Display a text box and return a non empty String

getInt :: (FormInput view, MonadIO m) => Maybe Int -> View view m Int Source

Display a text box and return a Int (if the value entered is not an Int, fails the validation)

getInteger :: (FormInput view, MonadIO m) => Maybe Integer -> View view m Integer Source

Display a text box and return an Integer (if the value entered is not an Integer, fails the validation)

getTextBox :: (FormInput view, Monad m, Typeable a, Show a, Read a) => Maybe a -> View view m a Source

getMultilineText :: (FormInput view, Monad m) => Text -> View view m Text Source

Display a multiline text box and return its content

getBool :: (FormInput view, Monad m, Functor m) => Bool -> String -> String -> View view m Bool Source

Display a dropdown box with the two values (second (true) and third parameter(false)) . With the value of the first parameter selected.

getSelect :: (FormInput view, Monad m, Typeable a, Read a) => View view m (MFOption a) -> View view m a Source

Display a dropdown box with the options in the first parameter is optionally selected . It returns the selected option.

setOption :: (Monad m, Show a, Eq a, Typeable a, FormInput view) => a -> view -> View view m (MFOption a) Source

Set the option for getSelect. Options are concatenated with <|>

setSelectedOption :: (Monad m, Show a, Eq a, Typeable a, FormInput view) => a -> view -> View view m (MFOption a) Source

Set the selected option for getSelect. Options are concatenated with <|>

getPassword :: (FormInput view, Monad m) => View view m String Source

Display a password box

getRadio :: (Monad m, Functor m, FormInput view) => [String -> View view m (Radio a)] -> View view m a Source

encloses a set of Radio boxes. Return the option selected

setRadio :: (FormInput view, MonadIO m, Read a, Typeable a, Eq a, Show a) => a -> String -> View view m (Radio a) Source

Implement a radio button the parameter is the name of the radio group

setRadioActive :: (FormInput view, MonadIO m, Read a, Typeable a, Eq a, Show a) => a -> String -> View view m (Radio a) Source

Implement a radio button that perform a submit when pressed. the parameter is the name of the radio group

wlabel :: (Monad m, FormInput view) => view -> View view m a -> View view m a Source

getCheckBoxes :: (FormInput view, Monad m) => View view m CheckBoxes -> View view m [String] Source

genCheckBoxes :: (Monad m, FormInput view) => view -> View view m CheckBoxes Source

Read the checkboxes dynamically created by JavaScript within the view parameter see for example selectAutocomplete in MFlow.Forms.Widgets

setCheckBox :: (FormInput view, MonadIO m) => Bool -> String -> View view m CheckBoxes Source

Display a text box and return the value entered if it is readable( Otherwise, fail the validation)

submitButton :: (FormInput view, Monad m) => String -> View view m String Source

resetButton :: (FormInput view, Monad m) => String -> View view m () Source

whidden :: (Monad m, FormInput v, Read a, Show a, Typeable a) => a -> View v m a Source

wlink :: (Typeable a, Show a, MonadIO m, FormInput view) => a -> view -> View view m a Source

Creates a link to a the next step within the flow. A link can be composed with other widget elements. It can not be broken by its own definition. It points to the page that created it.

absLink :: (FormInput v, MonadIO m, Typeable * a, Show a) => a -> v -> View v m a Source

Creates an absolute link. While a wlink path depend on the page where it is located and ever points to the code of the page that had it inserted, an absLink point to the first page in the flow that inserted it. It is useful for creating a backtracking point in combination with retry

  page $ absLink "here" << p << "here link"
  page $ p << "second page" ++> wlink () << p << "click here"
  page $ p << "third page" ++> retry (absLink "here" << p << "will go back")
  page $ p << "fourth page" ++> wlink () << p << "will not reach here"

After navigating to the third page, when clicking in the link, will backtrack to the first, and will validate the first link as if the click where done in the first page. Then the second page would be displayed.

In monadic widgets, it also backtrack to the statement where the absLink is located without the need of retry:

  page $ do
    absLink "here" << p << "here link"
    p << "second statement" ++> wlink () << p << "click here"
    p << "third statement" ++> (absLink "here" << p << "will present the first statement alone")
    p << "fourth statement" ++> wlink () << p << "will not reach here"

absLink x = wcached (show x) 0 . wlink x

getKeyValueParam :: (FormInput view, MonadState (MFlowState view) m, Typeable * a, Read a) => String -> m (Maybe a) Source

return the value of a post or get param in the form ?param=value&param2=value2...

fileUpload Source

Arguments

:: (FormInput view, Monad m, Functor m) 
=> View view m (String, String, String)

( original file, file type, temporal uploaded)

upload a file to a temporary file in the server

The user can move, rename it etc.

returning :: (Typeable a, Read a, Show a, Monad m, FormInput view) => ((a -> String) -> view) -> View view m a Source

When some user interface return some response to the server, but it is not produced by a form or a link, but for example by an script, returning convert this code into a widget.

At runtime the parameter is read from the environment and validated.

. The parameter is the visualization code, that accept a serialization function that generate the server invocation string, used by the visualization to return the value by means of an script, usually.

wform :: (Monad m, FormInput view) => View view m b -> View view m b Source

Wrap a widget with form element within a form-action element. Usually this is not necessary since this wrapping is done automatically by the View monad, unless there are more than one form in the page.

firstOf :: (FormInput view, Monad m, Functor m) => [View view m a] -> View view m a Source

Concat a list of widgets of the same type, return a the first validated result

manyOf :: (FormInput view, MonadIO m, Functor m) => [View view m a] -> View view m [a] Source

from a list of widgets, it return the validated ones.

allOf :: (FormInput view, MonadIO m, IsString view, Functor m) => [View view m a] -> View view m [a] Source

like manyOf, but does not validate if one or more of the widgets does not validate

wraw :: Monad m => view -> View view m () Source

Render raw view formatting. It is useful for displaying information.

wrender :: (Monad m, Functor m, Show a, FormInput view) => a -> View view m a Source

Render a Show-able value and return it

notValid :: Monad m => view -> View view m a Source

FormLet modifiers

validate :: (FormInput view, Monad m) => View view m a -> (a -> WState view m (Maybe view)) -> View view m a Source

Validates a form or widget result against a validating procedure

getOdd= getInt Nothing validate (x -> return $ if mod x 2==0 then  Nothing else Just "only odd numbers, please")

noWidget :: (FormInput view, Monad m, Functor m) => View view m a Source

Empty widget that does not validate. May be used as "empty boxes" inside larger widgets.

It returns a non valid value.

stop :: (FormInput view, Monad m, Functor m) => View view m a Source

a synonym of noWidget that can be used in a monadic expression in the View monad does not continue

waction :: (FormInput view, Monad m) => View view m a -> (a -> FlowM view m b) -> View view m b Source

Actions are callbacks that are executed when a widget is validated. A action may be a complete flow in the flowM monad. It takes complete control of the navigation while it is executed. At the end it return the result to the caller and display the original calling page. It is useful when the widget is inside widget containers that may treat it as a black box.

It returns a result that can be significant or, else, be ignored with <** and **>. An action may or may not initiate his own dialog with the user via ask

wcallback :: Monad m => View view m a -> (a -> View view m b) -> View view m b Source

It is a callback in the view monad. The callback rendering substitutes the widget rendering when the latter is validated, without affecting the rendering of other widgets. This allow the simultaneous execution of different behaviors in different widgets in the same page. The inspiration is the callback primitive in the Seaside Web Framework that allows similar functionality (See http://www.seaside.st)

This is the visible difference with waction callbacks, which execute a a flow in the FlowM monad that takes complete control of the navigation, while wactions are executed within the same page.

wmodify :: (Monad m, FormInput v) => View v m a -> (v -> Maybe a -> WState v m (v, Maybe b)) -> View v m b Source

change the rendering and the return value of a page. This is superseded by page flows.

Caching widgets

cachedWidget Source

Arguments

:: (MonadIO m, Typeable view, FormInput view, Typeable a, Executable m) 
=> String

The key of the cached object for the retrieval

-> Int

Timeout of the caching. Zero means the whole server run

-> View view Identity a

The cached widget, in the Identity monad

-> View view m a

The cached result

Cached widgets operate with widgets in the Identity monad, but they may perform IO using the execute instance of the monad m, which is usually the IO monad. execute basically "sanctifies" the use of unsafePerformIO for a transient purpose such is caching. This is defined in Data.TCache.Memoization. The programmer can create his own instance for his monad.

With cachedWidget it is possible to cache the rendering of a widget as a ByteString (maintaining type safety) , permanently or for a certain time. this is very useful for complex widgets that present information. Specially it they must access to databases.

import MFlow.Wai.Blaze.Html.All
import Some.Time.Library
addMessageFlows [(noscript, time)]
main= run 80 waiMessageFlow
time=do  ask $ cachedWidget "time" 5
             $ wlink () b << "the time is " ++ show (execute giveTheTime) ++ " click here"
             time

this pseudocode would update the time every 5 seconds. The execution of the IO computation giveTheTime must be executed inside the cached widget to avoid unnecesary IO executions.

NOTE: the rendering of cached widgets are shared by all users

wcached Source

Arguments

:: (MonadIO m, Typeable view, FormInput view, Typeable a, Executable m) 
=> String

The key of the cached object for the retrieval

-> Int

Timeout of the caching. Zero means sessionwide

-> View view Identity a

The cached widget, in the Identity monad

-> View view m a

The cached result

A shorter name for cachedWidget

wfreeze Source

Arguments

:: (MonadIO m, Typeable view, FormInput view, Typeable a, Executable m) 
=> String

The key of the cached object for the retrieval

-> Int

Timeout of the caching. Zero means sessionwide

-> View view m a

The cached widget

-> View view m a

The cached result

Unlike cachedWidget, which cache the rendering but not the user response, wfreeze cache also the user response. This is useful for pseudo-widgets which just show information while the controls are in other non freezed widgets. A freezed widget ever return the first user response It is faster than cachedWidget. It is not restricted to the Identity monad.

NOTE: the content of freezed widgets are shared by all users

Widget combinators

(<+>) :: (Monad m, FormInput view) => View view m a -> View view m b -> View view m (Maybe a, Maybe b) infixr 2 Source

Join two widgets in the same page the resulting widget, when asked with it, return a 2 tuple of their validation results if both return Noting, the widget return Nothing (invalid).

it has a low infix priority: infixr 2

r <- ask  widget1 <+>  widget2
case r of (Just x, Nothing) -> ..

(|*>) :: (MonadIO m, Functor m, FormInput view) => View view m r -> [View view m r'] -> View view m (Maybe r, Maybe r') infixr 5 Source

Intersperse a widget in a list of widgets. the results is a 2-tuple of both types.

it has a infix priority infixr 5

(|+|) :: (Functor m, FormInput view, MonadIO m) => View view m r -> View view m r' -> View view m (Maybe r, Maybe r') infixr 1 Source

Put a widget before and after other. Useful for navigation links in a page that appears at toAdd and at the bottom of a page.

(**>) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m b infixr 1 Source

The first elem result (even if it is not validated) is discarded, and the second is returned . This contrast with the applicative operator *> which fails the whole validation if the validation of the first elem fails.

The first element is displayed however, as happens in the case of *> .

Here w's are widgets and r's are returned values

(w1 <* w2) will return Just r1 only if w1 and w2 are validated

(w1 <** w2) will return Just r1 even if w2 is not validated

it has a low infix priority: infixr 1

(<**) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m a infixr 1 Source

The second elem result (even if it is not validated) is discarded, and the first is returned . This contrast with the applicative operator *> which fails the whole validation if the validation of the second elem fails. The second element is displayed however, as in the case of <*. see the <** examples

it has a low infix priority: infixr 1

(<|>) :: Alternative f => forall a. f a -> f a -> f a

An associative binary operation

(<*) :: Applicative f => forall a b. f a -> f b -> f a

Sequence actions, discarding the value of the second argument.

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4

An infix synonym for fmap.

(<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b

Sequential application.

(>:>) :: (Monad m, Monoid v) => View v m a -> View v m [a] -> View v m [a] Source

Formatting combinators

(<<<) :: (Monad m, Monoid view) => (view -> view) -> View view m a -> View view m a infixr 5 Source

Enclose Widgets within some formatting. view is intended to be instantiated to a particular format

NOTE: It has a infix priority : infixr 5 less than the one of ++> and <++ of the operators, so use parentheses when appropriate, unless the we want to enclose all the widgets in the right side. Most of the type errors in the DSL are due to the low priority of this operator.

This is a widget, which is a table with some links. it returns an Int

 import MFlow.Forms.Blaze.Html

 tableLinks :: View Html Int
 table ! At.style "border:1;width:20%;margin-left:auto;margin-right:auto"
            <<< caption << text "choose an item"
            ++> thead << tr << ( th << b << text  "item" <> th << b << text "times chosen")
            ++> (tbody
                 <<< tr ! rowspan "2" << td << linkHome
                 ++> (tr <<< td <<< wlink  IPhone (b << text "iphone") <++  td << ( b << text (fromString $ show ( cart V.! 0)))
                 <|>  tr <<< td <<< wlink  IPod (b << text "ipad")     <++  td << ( b << text (fromString $ show ( cart V.! 1)))
                 <|>  tr <<< td <<< wlink  IPad (b << text "ipod")     <++  td << ( b << text (fromString $ show ( cart V.! 2))))
                 )

(++>) :: (Monad m, Monoid view) => view -> View view m a -> View view m a infixr 6 Source

Prepend formatting code to a widget

bold << "enter name" ++> getString Nothing

It has a infix priority: infixr 6 higher than <<< and most other operators

(<++) :: (Monad m, Monoid v) => View v m a -> v -> View v m a infixr 6 Source

Append formatting code to a widget

 getString "hi" <++ H1 << "hi there"

It has a infix priority: infixr 6 higher than <<< and most other operators.

(<!) :: (FormInput view, Monad m) => View view m a -> Attribs -> View view m a infixl 8 Source

Add attributes to the topmost tag of a widget

It has a fixity infix 8

ByteString tags

btag :: String -> Attribs -> ByteString -> ByteString Source

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 -> ByteString Source

bhtml ats v= btag "html" ats v

bbody :: Attribs -> ByteString -> ByteString Source

bbody ats v= btag "body" ats v

send raw bytestring data

rawSend :: (FormInput v, MonadIO m, Functor m) => ByteString -> View v m () Source

send raw bytestring data to the client. usable for

example

do

setHttpHeader Content-Type "text//plain" maxAge 36000 rawSend longdata

Normalization

flatten :: Flatten (Maybe tree) list => tree -> list Source

Flatten a binary tree of tuples of Maybe results produced by the <+> operator into a single tuple with the same elements in the same order. This is useful for easing matching. For example:

 res <- ask $ wlink1 <+> wlink2 wform <+> wlink3 <+> wlink4

res has type:

Maybe (Maybe (Maybe (Maybe (Maybe a,Maybe b),Maybe c),Maybe d),Maybe e)

but flatten res has type:

 (Maybe a, Maybe b, Maybe c, Maybe d, Maybe e)

normalize :: (Monad m, FormInput v) => View v m a -> View ByteString m a Source

Running the flow monad

runFlow :: (FormInput view, MonadIO m) => FlowM view (Workflow m) () -> Token -> Workflow m () Source

Execute the Flow, in the FlowM view m monad. It is used as parameter of hackMessageFlow waiMessageFlow or addMessageFlows

The flow is executed in a loop. When the flow is finished, it is started again

main= do
   addMessageFlows [("noscript",transient $ runFlow mainf)]
   forkIO . run 80 $ waiMessageFlow
   adminLoop

transientNav :: (Serialize a, Typeable view, FormInput view, Typeable a) => FlowM view IO a -> FlowM view (Workflow IO) a Source

To execute transient flows as if they were persistent, it can be used instead of step, but it does log nothing. Thus, it is faster and convenient when no session state must be stored beyond the lifespan of the server process.

transient $ runFlow f === runFlow $ transientNav f

runFlowOnce :: (FormInput view, MonadIO m) => FlowM view (Workflow m) () -> Token -> Workflow m () Source

runFlowIn :: (MonadIO m, FormInput view) => String -> FlowM view (Workflow IO) b -> FlowM view m b Source

Run a persistent flow inside the current flow. It is identified by the procedure and the string identifier. Unlike the normal flows, that run within infinite loops, runFlowIn executes once. In subsequent executions, the flow will get the intermediate responses from the log and will return the result without asking again. This is useful for asking once, storing in the log and subsequently retrieving user defined configurations by means of persistent flows with web formularies.

runFlowConf :: (FormInput view, MonadIO m) => FlowM view m a -> m a Source

To unlift a FlowM computation. useful for executing the configuration generated by runFLowIn outside of the web flow (FlowM) monad

step :: (Serialize a, Typeable view, FormInput view, MonadIO m, Typeable a) => FlowM view m a -> FlowM view (Workflow m) a Source

Stores the result of the flow in a persistent log. When restarted, it get the result from the log and it does not execute it again. When no results are in the log, the computation is executed. It is equivalent to step but in the FlowM monad.

controlling backtracking

goingBack :: MonadState (MFlowState view) m => m Bool Source

True if the flow is going back (as a result of the back button pressed in the web browser). Usually this check is nos necessary unless conditional code make it necessary

menu= do
       mop <- getGoStraighTo
       case mop of
        Just goop -> goop
        Nothing -> do
               r <- ask option1 <|> option2
               case r of
                op1 -> setGoStraighTo (Just goop1) >> goop1
                op2 -> setGoStraighTo (Just goop2) >> goop2

This pseudocode below would execute the ask of the menu once. But the user will never have the possibility to see the menu again. To let him choose other option, the code has to be change to

menu= do
       mop <- getGoStraighTo
       back <- goingBack
       case (mop,back) of
        (Just goop,False) -> goop
        _ -> do
               r <- ask option1 <|> option2
               case r of
                op1 -> setGoStraighTo (Just goop1) >> goop1
                op2 -> setGoStraighTo (Just goop2) >> goop2

However this is very specialized. Normally the back button detection is not necessary. In a persistent flow (with step) even this default entry option would be completely automatic, since the process would restart at the last page visited.

returnIfForward :: (Monad m, FormInput view, Functor m) => b -> View view m b Source

return the result if going forward

If the process is backtracking, it does not validate, in order to continue the backtracking

breturn :: Monad m => a -> FlowM v m a Source

Use this instead of return to return from a computation with ask statements

This way when the user press the back button, the computation will execute back, to the returned code, according with the user navigation.

preventGoingBack :: (Functor m, MonadIO m, FormInput v) => FlowM v m () -> FlowM v m () Source

Will prevent the Suprack beyond the point where preventGoingBack is located. If the user press the back button beyond that point, the flow parameter is executed, usually it is an ask statement with a message. If the flow is not going back, it does nothing. It is a cut in Supracking

It is useful when an undoable transaction has been commited. For example, after a payment.

This example show a message when the user go back and press again to pay

  ask $ wlink () << b << "press here to pay 100000 $ "
  payIt
  preventGoingBack . ask $   b << "You  paid 10000 $ one time"
                         ++> wlink () << b << " Please press here to complete the proccess"
  ask $ wlink () << b << "OK, press here to go to the menu or press the back button to verify that you can not pay again"
  where
  payIt= liftIO $ print "paying"

compensate :: Monad m => m a -> m a -> FlowM v m a Source

less powerful version of onBacktrack: The second computation simply undo the effect of the first one, and the flow continues backward ever. It can be used as a rollback mechanism in the context of long running transactions.

onBacktrack :: Monad m => m a -> FlowM v m a -> FlowM v m a Source

executes the first computation when going forward and the second computation when backtracking. Depending on how the second computation finishes, the flow will resume forward or backward.

retry :: Monad m => View v m a -> View v m () Source

forces backtracking if the widget validates, because a previous page handle this widget response . This is useful for recurrent cached widgets or absLinks that are present in multiple pages. For example in the case of menus or common options. The active elements of this widget must be cached with no timeout.

Setting parameters

setHttpHeader Source

Arguments

:: MonadState (MFlowState view) m 
=> ByteString

name

-> ByteString

value

-> m () 

Set an HTTP Response header

setHeader :: MonadState (MFlowState view) m => (view -> view) -> m () Source

Set the header-footer that will enclose the widgets. It must be provided in the same formatting than them, although with normalization to ByteStrings any formatting can be used

This header uses XML trough Haskell Server Pages (http://hackage.haskell.org/package/hsp)

setHeader $ c ->
           <html>
                <head>
                     <title>  my title </title>
                     <meta name= "Keywords" content= "sci-fi" />)
                </head>
                 <body style= "margin-left:5%;margin-right:5%">
                      <% c %>
                 </body>
           </html>

This header uses Text.XHtml

setHeader $ c ->
          thehtml
              << (header
                  << (thetitle << title +++
                      meta ! [name "Keywords",content "sci-fi"])) +++
                 body ! [style "margin-left:5%;margin-right:5%"] c

This header uses both. It uses byteString tags

setHeader $ c ->
         bhtml [] $
              btag "head" [] $
                    (toByteString (thetitle << title) append
                    toByteString name= "Keywords" content= "sci-fi" /) append
                 bbody [("style", "margin-left:5%;margin-right:5%")] c

addHeader :: Monad m => (view -> view) -> FlowM view m () Source

Add another header embedded in the previous one

getHeader :: Monad m => FlowM view m (view -> view) Source

Return the current header

setSessionData :: (Typeable a, MonadState (MFlowState view) m) => a -> m () Source

Set user-defined data in the context of the session.

The data is indexed by type in a map. So the user can insert-retrieve different kinds of data in the session context.

This example define addHistory and getHistory to maintain a Html log in the session of a Flow:

newtype History = History ( Html) deriving Typeable
setHistory html= setSessionData $ History html
getHistory= getSessionData `onNothing` return (History mempty) >>= \(History h) -> return h
addHistory html= do
     html' <- getHistory
     setHistory $ html' `mappend` html

getSessionData :: (Typeable a, MonadState (MFlowState view) m) => m (Maybe a) Source

Get the session data of the desired type if there is any.

getSData :: (Monad m, Typeable a, Monoid v) => View v m a Source

getSessionData specialized for the View monad. if Nothing, the monadic computation does not continue.

delSessionData :: (MonadState (MFlowState view) m, Typeable * a) => a -> m () Source

setTimeouts :: MonadState (MFlowState v) m => Int -> Integer -> m () Source

Set 1) the timeout of the flow execution since the last user interaction. Once passed, the flow executes from the beginning.

2) In persistent flows it set the session state timeout for the flow, that is persistent. If the flow is not persistent, it has no effect.

As the other state primitives, it can be run in the Flow and in the View monad

transient flows restart anew. persistent flows (that use step) restart at the last saved execution point, unless the session time has expired for the user.

Cookies

setCookie Source

Arguments

:: MonadState (MFlowState view) m 
=> String

name

-> String

value

-> String

path

-> Maybe Integer

Max-Age in seconds. Nothing for a session cookie

-> m () 

Set an HTTP cookie

setParanoidCookie Source

Arguments

:: MonadState (MFlowState view) m 
=> String

name

-> String

value

-> String

path

-> Maybe Integer

Max-Age in seconds. Nothing for a session cookie

-> m () 

setEncryptedCookie Source

Arguments

:: MonadState (MFlowState view) m 
=> String

name

-> String

value

-> String

path

-> Maybe Integer

Max-Age in seconds. Nothing for a session cookie

-> m () 

Ajax

ajax Source

Arguments

:: (MonadIO m, FormInput v) 
=> (String -> View v m ByteString)

user defined procedure, executed in the server.Receives the value of the JavaScript expression and must return another JavaScript expression that will be executed in the web browser

-> View v m (String -> String)

returns a function that accept a JavaScript expression and return a JavaScript event handler expression that invokes the ajax server procedure

Install the server code and return the client code for an AJAX interaction. It is very lightweight, It does no t need jQuery.

This example increases the value of a text box each time the box is clicked

 ask $ do
       let elemval= "document.getElementById('text1').value"
       ajaxc <- ajax $ \n -> return $ elemval <> "='" <> B.pack(show(read  n +1)) <> "'"
       b <<  text "click the box"
         ++> getInt (Just 0) <! [("id","text1"),("onclick", ajaxc elemval)]

ajaxSend :: (Read a, Monoid v, MonadIO m) => View v m ByteString -> View v m a Source

Send the JavaScript expression, generated by the procedure parameter as a ByteString, execute it in the browser and the result is returned back

The ajaxSend invocation must be inside a ajax procedure or else a No ajax session set error will be produced

ajaxSend_ :: (MonadIO m, Monoid v) => View v m ByteString -> View v m () Source

Like ajaxSend but the result is ignored

Requirements

class Requirements a where Source

Methods

installRequirements :: (MonadState (MFlowState view) m, MonadIO m, FormInput view) => [a] -> m view Source

data WebRequirement Source

Constructors

JScriptFile String [String]

Script URL and the list of scripts to be executed when loaded

CSSFile String

a CSS file URL

CSS String

a String with a CSS description

JScript String

a string with a valid JavaScript

ServerProc (String, Flow)

a server procedure

requires :: (Requirements a, MonadState (MFlowState view) m, Typeable * a, Show a) => [a] -> m () Source

Requirements are JavaScripts, Stylesheets or server processes (or any instance of the Requirement class) that are included in the Web page or in the server when a widget specifies this. requires is the procedure to be called with the list of requirements. Various widgets in the page can require the same element, MFlow will install it once.

Utility

getSessionId :: MonadState (MFlowState v) m => m String Source

Return the session identifier

getLang :: MonadState (MFlowState view) m => m String Source

Return the user language. Now it is fixed to "en"

genNewId :: MonadState (MFlowState view) m => m String Source

Generate a new string. Useful for creating tag identifiers and other attributes.

If the page is refreshed, the identifiers generated are the same.

getNextId :: MonadState (MFlowState view) m => m String Source

Get the next identifier that will be created by genNewId

changeMonad :: (Monad m, Executable m') => View v m' a -> View v m a Source

Execute the widget in a monad and return the result in another.