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

Safe HaskellNone

MFlow.Forms

Contents

Description

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 processses 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 function. Allthoug 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 functionalities 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, callbaks 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 programer 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 shutdowm, 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 posssible to combine links and forms in the same widget by using applicative combinators but also additional applicative combinators like <+> !*> , |*|.

  • NEW IN THIS RELEASE:
Back Button
This is probably the first implementation of an stateful Web framework that 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 initate a flow of interactions with the user or simply execute an internal computation. Callbacks are necessary for the creation of abstract container widgets that may not know the behaviour of its content. 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
it is not only possible to add Html formatting, but also to add atributes to a formlet element. This example has three formLet elements with the attribute size added, and a string prepended to the second password box.
userFormLine=
       (User <$> getString (Just enter user)                  <! [(size,5)]
             <*> getPassword                                    <! [(size,5)]
             <+> submitButton login)
             <+> fromString   password again ++> getPassword  <! [(size,5)]
             <*  submitButton register
ByteString normalization and hetereogeneous formatting
For caching the rendering of widgets at the ByteString level, and to permit many formatring 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.
AJAX
See MFlow.Forms.Ajax
File Server
With file caching. See MFlow.FileServer

This is a complete example, that can be run with runghc, which show some of these features:

 
 module Main where
 import MFlow.Wai.XHtml.All
 import Data.TCache
 import Control.Monad.Trans
 import Data.Typeable
 import Control.Concurrent
 import Control.Exception as E
 import qualified Data.ByteString.Char8 as SB
 import qualified Data.Vector as V
 import Data.Maybe

 data Ops= Ints | Strings | Actions | Ajax | Opt deriving(Typeable,Read, Show)
 main= do
    setFilesPath ""
    addFileServerWF
    addMessageFlows [(""  ,transient $ runFlow mainf)
                    ,("shop"    ,runFlow shopCart)]
    forkIO $ run 80 waiMessageFlow
    adminLoop

 stdheader c= p << "you can press the back button to go to the menu"+++ c

 mainf=   do
        setHeader stdheader
        r <- ask $   wlink Ints (bold << "increase an Int")
                <|>  br ++> wlink Strings (bold << "increase a String")
                <|>  br ++> wlink Actions (bold << "Example of a string widget with an action")
                <|>  br ++> wlink Ajax (bold << "Simple AJAX example")
                <|>  br ++> wlink Opt (bold << "select options")
                <++ (br +++ linkShop) -- this is an ordinary XHtml link

        case r of
          Ints    ->  clickn 0
          Strings ->  clicks "1"
          Actions ->  actions 1
          Ajax    ->  ajaxsample
          Opt     ->  options
        mainf
     where
     linkShop= toHtml $ hotlink  "shop" << "shopping"

 options= do
    r <- ask $ getSelect (setOption "blue" (bold << "blue")   <|>
                          setSelectedOption "Red"  (bold << "red")  ) <! dosummit
    ask $ p << (r ++ " selected") ++> wlink () (p<< " menu")
    breturn()
    where
    dosummit= [("onchange","this.form.submit()")]

 clickn (n :: Int)= do
    setHeader stdheader
    r <- ask $  wlink "menu" (p << "menu")
            |+| getInt (Just n) <* submitButton "submit"
    case r of
     (Just _,_) -> breturn ()
     (_, Just n') -> clickn $ n'+1


 clicks s= do
    setHeader stdheader
    s' <- ask $ (getString (Just s)
              <* submitButton "submit")
              `validate` (\s -> return $ if length s   > 5 then Just "length must be < 5" else Nothing )
    clicks $ s'++ "1"


 ajaxheader html= thehtml << ajaxHead << p << "click the box" +++ html

 ajaxsample= do
    setHeader ajaxheader
    ajaxc <- ajaxCommand "document.getElementById('text1').value"
                         (\n ->  return $ "document.getElementById('text1').value='"++show(read  n +1)++"'")
    ask $ (getInt (Just 0) <! [("id","text1"),("onclick", ajaxc)])
    breturn()

 actions n=do
   ask $ wlink () (p << "exit from action")
      <**((getInt (Just (n+1)) <** submitButton "submit" ) `waction` actions )
   breturn ()

 -- A persistent flow  (uses step). The process is killed after 10 seconds of inactivity
 -- but it is restarted automatically. if you restart the program, it remember the shopping cart
 -- defines a table with links enclosed that return ints and a link to the menu, that abandon this flow.
 shopCart  = do
    setTimeouts 10 0
    shopCart1 (V.fromList [0,0,0:: Int])
    where
    shopCart1 cart=  do
      i <- step . ask $
              table ! [border 1,thestyle "width:20%;margin-left:auto;margin-right:auto"]
              <<< caption << "choose an item"
              ++> thead << tr << concatHtml[ th << bold << "item", th << bold << "times chosen"]
              ++> (tbody
                   <<<  tr ! [rowspan 2] << td << linkHome
                   ++> (tr <<< td <<< wlink  0 (bold <<"iphone") <++  td << ( bold << show ( cart V.! 0))
                   <|>  tr <<< td <<< wlink  1 (bold <<"ipad")   <++  td << ( bold << show ( cart V.! 1))
                   <|>  tr <<< td <<< wlink  2 (bold <<"ipod")   <++  td << ( bold << show ( cart V.! 2)))
                   <++  tr << td << linkHome
                   )

      let newCart= cart V.// [(i, cart V.! i + 1 )]
      shopCart1 newCart
     where
     linkHome= (toHtml $ hotlink  noScript << bold << "home")

Synopsis

Basic definitions

class (Functor m, MonadIO m) => FormLet a m view whereSource

A FormLet instance

Methods

digest :: Maybe a -> View view m aSource

Instances

(Functor m, MonadIO m, FormInput view, FormLet a m view, FormLet b m view) => FormLet (a, b) m view 
(Functor m, MonadIO m, FormInput view, FormLet a m view, FormLet b m view, FormLet c m view) => FormLet (a, b, c) m view 

type FlowM view m = BackT (WState view m)Source

data View v m a Source

Instances

MonadTrans (View view) 
(Monad (View view m), Functor m, Monad m) => MonadState (MFlowState view) (View view m) 
(Monad m, Functor m) => Monad (View view m) 
(Monad m, Functor m) => Functor (View view m) 
(Functor (View view m), Functor m, Monad m) => Applicative (View view m) 
(Applicative (View view m), Functor m, Monad m) => Alternative (View view m) 
(Monad (View view m), MonadIO m, Functor m) => MonadIO (View view m) 
Monad m => ADDATTRS (View Html m a) 

class Monoid view => FormInput view whereSource

Minimal interface for defining the basic form combinators in a concrete rendering. defined in this module. see MFlow.Forms.XHtml for the instance for Text.XHtml and MFlow.Forms.HSP for an instance form Haskell Server Pages.

Methods

inred :: view -> viewSource

fromString :: String -> viewSource

flink :: String -> view -> viewSource

flink1 :: String -> viewSource

finput :: Name -> Type -> Value -> Checked -> OnClick -> viewSource

ftextarea :: String -> String -> viewSource

fselect :: String -> view -> viewSource

foption :: String -> view -> Bool -> viewSource

foption1 :: String -> Bool -> viewSource

formAction :: String -> view -> viewSource

addAttributes :: view -> Attribs -> viewSource

Users

userRegister :: MonadIO m => String -> String -> m (DBRef User)Source

Register an user/password

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

Authentication against userRegistered users. to be used with validate

isLogged :: MonadState (MFlowState v) m => m BoolSource

Wether the user is logged or is anonymous

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

getAdminName :: MonadIO m => m UserStrSource

getUserSimple :: (FormInput view, Monoid view, Typeable view, ToHttpData view, MonadIO m, Functor m) => FlowM view m StringSource

If not logged, perform login. otherwise return the user

getUserSimple= getUser Nothing userFormLine

getUser :: (FormInput view, Monoid view, Typeable view, ToHttpData view, MonadIO m, Functor m) => Maybe String -> View view m (Maybe (Maybe (UserStr, PasswdStr), Maybe String), Maybe String) -> FlowM view m StringSource

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, Monoid view, Functor m, Monad m) => View view m (Maybe (Maybe (UserStr, PasswdStr), Maybe String), Maybe String)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 loging, a entry to repeat password necesary 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")
     <+> fromString "  password again" +> getPassword <* submitButton "register"

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

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

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

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. Otherwise, if the user is already logged, the widget does not appear If the user press the register button, the user/password is registered and the user

User interaction

ask :: (ToHttpData view, FormInput view, Monoid view, MonadIO m, Typeable view) => View view m b -> FlowM view m bSource

It is the way to interact with the user. It takes a widget and return the user result If the environment has the result, ask don't ask to the user. To force asking in any case, put an clearEnv statement before in the FlowM monad

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

Clears the environment

formLets

they mimic the HTML form elements. It is possible to modify their attributes with the <! operator. They are combined with the widget combinators. formatting can be added with the formatting combinators. modifiers change their presentation and behaviour

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

display a text box and return a String

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

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

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

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 aSource

getMultilineText :: (FormInput view, Monad m) => String -> View view m StringSource

display a multiline text box and return its content

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

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 aSource

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

setOption :: (Monad m, Show 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, 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 StringSource

display a password box

getRadio :: (FormInput view, Functor m, MonadIO m) => String -> String -> View view m StringSource

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

getRadioActive :: (FormInput view, Functor m, MonadIO m) => String -> String -> View view m StringSource

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

getCheckBox :: (FormInput view, Functor m, MonadIO m) => String -> Bool -> View view m StringSource

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

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

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

creates a link wiget. A link can be composed with other widget elements,

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

wrap a widget of form element within a form-action element.

FormLet modifiers

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

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) => View view m aSource

empty widget that return Nothing. May be used as "empty boxes" inside larger widgets

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

render the Show instance of the parameter and return it. It is useful for displaying information

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

Actions are callbacks that are executed when a widget is validated. It is useful when the widget is inside widget containers that know nothing about his content. It returns a result that can be significative or, else, be ignored with <** and **>. An action may or may not initiate his own dialog with the user via ask

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

A modifier get the result and the rendering of a widget and change them.

This modifier, when logged, changes a login-password-register widget with a display username.

userFormOrName= userWidget Nothing userFormLine `wmodify` f
   where
   f _ justu@(Just u)  =  return ([fromString u], justu) -- user validated, display and return user
   f felem Nothing = do
     us <-  getCurrentUser
     if us == anonymous
           then return (felem, Nothing)                    -- user not logged, present the form
           else return([fromString us],  Just us)        -- already logged, display and return user

Caching widgets

cachedWidgetSource

Arguments

:: (Show a, MonadIO m, Typeable view, Monoid view, FormInput view, Typeable a, Functor m, 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

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 user 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.XHtm.All
 import Some.Time.Library
 addMessageFlows [(noscript, time)]
 main= run 80 waiMessageFlow
 time=do  ask $ cachedWidget "time" 5
            $ wlink () bold << "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.

Widget combinators

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

Join two widgets in the same page the resulting widget, when asked with it, returns a either one or the other

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

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

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

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

Put a widget above and below other. Useful for navigation links in a page.

(**>) :: (Functor m, Monad m) => View view m a -> View view m b -> View view m bSource

The first elem result (even if it is not validated) is discarded, and the secod 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 in the case of *>

(<**) :: (Functor m, Monad m) => View view m a -> View view m b -> View view m aSource

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 first element is displayed however, as in the case of <*

wconcat :: (Monoid view, MonadIO m, Functor m) => [View view m a] -> View view m aSource

Concat a list of widgets of the same type, to return a single result

(<|>) :: 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

An infix synonym for fmap.

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

Sequential application.

Normalized (convert to ByteString) widget combinators

these dot operators are indentical to the non dot operators, with the addition of the conversion of the arguments to lazy byteStrings

The purpose is to combine heterogeneous formats into byteString-formatted widgets that can be cached with cachedWidget

(.<+>.) :: (Monad m, ToByteString v, ToByteString v1) => View v m a -> View v1 m b -> View ByteString m (Maybe a, Maybe b)Source

 (.<+>.) x y = normalize x <+> normalize y

(.|*>.) :: (Functor m, MonadIO m, ToByteString v, ToByteString v1) => View v m r -> [View v1 m r'] -> View ByteString m (Maybe r, Maybe r')Source

 (.|*>.) x y = normalize x |*> map normalize y

(.|+|.) :: (Functor m, MonadIO m, ToByteString v, ToByteString v1) => View v m r -> View v1 m r' -> View ByteString m (Maybe r, Maybe r')Source

 (.|+|.) x y = normalize x |+| normalize y

(.**>.) :: (Monad m, Functor m, ToByteString v, ToByteString v1) => View v m a -> View v1 m b -> View ByteString m bSource

 (.**>.) x y = normalize x **> normalize y

(.<**.) :: (Monad m, Functor m, ToByteString v, ToByteString v1) => View v m a -> View v1 m b -> View ByteString m aSource

 (.<**.) x y = normalize x <** normalize y

(.<|>.) :: (Monad m, Functor m, ToByteString v, ToByteString v1) => View v m a -> View v1 m a -> View ByteString m aSource

 (.<|>.) x y= normalize x <|> normalize y

Formatting combinators

(<<<) :: (Monad m, Monoid view) => (view -> view) -> View view m a -> View view m aSource

Enclose Widgets in some formating. view is intended to be instantiated to a particular format

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

 import MFlow.Forms.XHtml

 tableLinks :: View Html Int
 tableLinks= table ! [border 1,thestyle "width:20%;margin-left:auto;margin-right:auto"]
              <<< caption << "choose an item"
              ++> thead << tr << concatHtml[ th << bold << "item", th << bold << "times chosen"]
              ++> (tbody
                   <<< (tr <<< td <<< wlink  0 (bold <<"iphone") <++  td << ( bold << "One")
                   <|>  tr <<< td <<< wlink  1 (bold <<"ipad")   <++  td << ( bold << "Two")
                   <|>  tr <<< td <<< wlink  2 (bold <<"ipod")   <++  td << ( bold << "Three"))
                   )

(<++) :: Monad m => View v m a -> v -> View v m aSource

Append formatting code to a widget

 getString hi <++ H1 << hi there

(++>) :: (Monad m, Monoid view) => view -> View view m a -> View view m aSource

Prepend formatting code to a widget

bold "enter name" ++ getString Nothing

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

add attributes to the form element if the view has more than one element, it is applied to the first

Normalized (convert to ByteString) formatting combinators

some combinators that convert the formatting of their arguments to lazy byteString

(.<<.) :: ToByteString view => (ByteString -> ByteString) -> view -> ByteStringSource

 (.<<.) w x = w $ toByteString x

(.<++.) :: (Monad m, ToByteString v, ToByteString v') => View v m a -> v' -> View ByteString m aSource

 (.<++.) x v= normalize x <++ toByteString v

(.++>.) :: (Monad m, ToByteString v, ToByteString v') => v -> View v' m a -> View ByteString m aSource

 (.++>.) v x= toByteString v ++> normalize x

ByteString tags

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

Normalization

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

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, ToByteString v) => View v m a -> View ByteString m aSource

Useful for the creation of pages using two or more views. For example HSP and Html. Because both have ConvertTo instances to ByteString, then it is possible to mix them via normalize:

 normalize widget  <+> normalize widget'

is equivalent to

 widget .<+>. widget'

Running the flow monad

runFlow :: (FormInput view, Monoid view, Monad m) => FlowM view m () -> Token -> m ()Source

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

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

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

goingBack :: MonadState (MFlowState view) m => m BoolSource

True if the flow is going back (as a result of the back button pressed in the web browser). Usually this chech 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 would execute the ask of the menu once. But if the user press the back button he will see again the menu. 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

breturn :: Monad m => a -> BackT m aSource

Use this instead of return to return from a computation with an ask statement

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

Setting parameters

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

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

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

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

return the current header

setTimeouts :: Monad m => Int -> Integer -> FlowM view m ()Source

Set 1) the timeout of the flow execution since the last user interaction. Once passed, the flow executes from the begining. 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.

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

Cookies

setCookieSource

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

Internal use

data MFlowState view Source

Instances

Typeable1 MFlowState 
(Monad (View view m), Functor m, Monad m) => MonadState (MFlowState view) (View view m) 
(FormInput v, Monoid v, Serialize a) => Serialize (a, MFlowState v)