MFlow-0.0.3: (Web) application server. Stateful server processes. Simple, statically correct widget combinators.

Safe HaskellSafe-Infered

MFlow.Forms

Contents

Description

This module defines an integrated way to interact with the user. ask is a single method of user interaction. it send user interfaces and return statically typed responses. The user interface definitions are based on the formLets interface

But additionally, unlike formLets in its current form, it permits the definition of widgets. A widget is data that, when renderized and interact with the user, return data, just like a formlet, but it hasn to be an HTML form. it can contain JavaScript, or additional Html decoration or it can use Ajax istead of form post for the interaction. There is an example of widget defined (Selection)

widgets (and formlets) can be combined in a sigle Html page. Here is a ready-to-run example that combines a Widget (Selection) and a HTML decorated formLet in the same page.

import MFlow.Hack.XHtml.All

import Data.Typeable
import Control.Monad.Trans
import qualified Data.Vector as V

main= do

putStrLn $ options messageFlows
   run 80 $ hackMessageFlow messageFlows
   where
   messageFlows=  [("main",  runFlow mainProds )
                  ,("hello", stateless hello)]
   options msgs= "in the browser choose\n\n" ++
     concat [ http://server/++ i ++ n | (i,_) <- msgs]

--an stateless procedure, as an example
hello :: Env -> IO String
hello env =  return  "hello, this is a stateless response"

data Prod= Prod{pname :: String, pprice :: Int} deriving (Typeable,Read,Show)

-- formLets can have Html formatting. Additional operators <++ <+> <<< ++> to XHtml formatting

instance FormLet Prod IO Html where
   digest mp= table <<< (
      Prod <$> tr <<< (td << "enter the name"  <++ td <<< getString (pname <$> mp))
           <*> tr <<< (td << "enter the price" <++ td <<< getInt ( pprice <$> mp)))

-- Here an example of predefined widget (Selection) that return an Int, combined in the same
-- page with the fromLet for the introduction of a product.
-- The result of the user interaction is Either one or the other value

shopProds :: V.Vector Int -> [Prod]
          -> View Html IO  (Either Int Prod)
shopProds cart products=

p << "----------------Shopping List--------------"
  <++
  widget(Selection{
       stitle = bold << "choose an item",
       sheader= [ bold << "item"   , bold << "price", bold << "times chosen"],
       sbody= [([toHtml pname, toHtml $ show pprice, toHtml $ show $ cart V.! i],i )
              | (Prod{..},i ) <- zip products [1..]]})

<+>
  p << "--------------Add a new product ---------------"
  <++
  table <<< (tr <<< td ! [valign "top"]
                          <<< widget (Form (Nothing :: Maybe Prod) )
             ++>
             tr << td ! [align "center"]
                          << hotlink  "hello"
                                      (bold << "Hello World"))

-- the header

appheader user forms= thehtml
         << body << dlist << (concatHtml
            [dterm <<("Hi "++ user)
            ,dterm << "This example contains two forms enclosed within user defined HTML formatting"
            ,dterm << "The first one is defined as a Widget, the second is a formlet formatted within a table"
            ,dterm << "both are defined using an extension of the FormLets concept"
            ,dterm << "the form results are statically typed"
            ,dterm << "The state is implicitly logged. No explicit handling of state"
            ,dterm << "The program logic is written as a procedure. Not    in request-response form. But request response is possible"
            ,dterm << "lifespan of the serving process and the execution state defined by the programmer"
            ,dterm << "user state is  automatically recovered after cold re-start"
            ,dterm << "transient, non persistent states possible."
            ])
            +++ forms

-- Here the procedure. It ask for either entering a new product
-- or to "buy" one of the entered products.
-- There is a timeout of ten minutes before the process is stopped
-- THERE IS A timeout of one day for the whole state so after this, the
-- user will see the list erased.
-- The state is user specific.

--mainProds ::  FlowM Html (Workflow IO) ()
mainProds   = do
   setTimeouts (10*60) (24*60*60)
   setHeader $ w -> bold << "Please enter userpassword (pepepepe)" +++ br +++ w

setHeader  $ appheader user
   mainProds1 [] $ V.fromList [0]
   where
   mainProds1  prods cart=  do
     mr <- step . ask  $ shopProds  cart prods
     case mr of
      Right prod -> mainProds1  (prod:prods) (V.snoc cart 0)
      Left i   -> do
         let newCart= cart V. [(i, cart V.! i + 1 )]
         mainProds1 prods newCart

Synopsis

Documentation

class (Functor m, MonadIO m) => Widget a b m view | a -> view whereSource

Methods

widget :: a -> View view m bSource

Instances

FormLet a m view => Widget (Maybe a) a m view 
(FormInput view, Monoid view, Widget a b m view) => Widget (Form a) b m view 
(MonadIO m, Functor m, FormInput view, Read a, Show a, Eq a, Typeable a) => Widget (Selection a view) a m view 
(MonadIO m, Functor m) => Widget (View view m a) a m view 

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

Methods

digest :: Maybe a -> View view m aSource

Instances

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

class Widget a b m view => Launchable a b m view Source

Launchable widgets create user requests. For example whatever piece containing a Form tag, a link with an embeeded Ajax invocation etc.

A FormLet for an input field can not be an instance of Launchable, for example to invoke it with ask, make the widget an instance of Launchable

Instances

(FormInput view, Monoid view, Widget a b m view) => Launchable (Form a) b m view 
(MonadIO m, Functor m, FormInput view, Typeable a, Show a, Read a, Eq a) => Launchable (Selection a view) a m view 
(MonadIO m, Functor m) => Launchable (View view m a) a m view 

type View view m a = FormT view (FlowM view m) aSource

class FormInput view whereSource

Minimal interface for defining the abstract basic form combinators defined in this module. see MFlow.Forms.XHtml for the instance for Text.XHtml format

Methods

inred :: view -> viewSource

ftable :: view -> [view] -> [[view]] -> viewSource

fromString :: String -> viewSource

flink :: String -> view -> viewSource

flink1 :: String -> viewSource

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

ftextarea :: String -> String -> viewSource

foption :: String -> [(String, String)] -> Maybe String -> viewSource

foption1 :: String -> [String] -> Maybe String -> viewSource

fformAction :: String -> view -> viewSource

Instances

newtype FormT view m a Source

Constructors

FormT 

Fields

runFormT :: Params -> m (FormElm view a)
 

Instances

(Monad m, Functor m) => Monad (FormT view m) 
Functor m => Functor (FormT view m) 
(Functor m, Monad m) => Applicative (FormT view m) 
(MonadIO m, Functor m) => Widget (View view m a) a m view 
(MonadIO m, Functor m) => Launchable (View view m a) a m view 

data FormElm view a Source

Constructors

FormElm [view] (Maybe a) 

Instances

Functor (FormElm view) 

newtype Form a Source

Constructors

Form a 

Instances

(FormInput view, Monoid view, Widget a b m view) => Widget (Form a) b m view 
(FormInput view, Monoid view, Widget a b m view) => Launchable (Form a) b m view 

data Selection a view Source

Constructors

Selection 

Fields

stitle :: view
 
sheader :: [view]
 
sbody :: [([view], a)]
 

Instances

(MonadIO m, Functor m, FormInput view, Read a, Show a, Eq a, Typeable a) => Widget (Selection a view) a m view 
(MonadIO m, Functor m, FormInput view, Typeable a, Show a, Read a, Eq a) => Launchable (Selection a view) a m view 

userRegister :: String -> String -> IO (DBRef User)Source

register an user/password combination

userAuthenticate :: MonadIO m => User -> m (Maybe String)Source

authentication against userRegistered users. to be used with validate

getUser :: (FormInput view, Monoid view, Typeable view, ConvertTo (HttpData view) display, Typeable display, MonadIO m, Functor m) => 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. It return a reference to the user.

user interaction

ask :: (Launchable a b m view, FormInput view, Monoid view, Typeable view, ConvertTo (HttpData view) display, Typeable display) => a -> FlowM view m bSource

it is the way to interact with the user. It takes a combination of launchable objects and return the user result in the FlowM monad

getters to be used in instances of FormLet and Widget in the Applicative style.

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

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

getOption :: (FormInput view, Monad m) => Maybe String -> [(String, String)] -> View view m StringSource

validate :: (FormInput view, Functor m, MonadIO m) => View view m a -> (a -> 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 number please)

mix :: (FormInput view, Monad m) => View view m a' -> View view m b' -> View view m (Either a' b')Source

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

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

encloses instances of Widget or FormLet in formating view is intended to be instantiated to a particular format see MFlow.Forms.XHtml for usage examples

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

append formatting to Widget or FormLet instances view is intended to be instantiated to a particular format see MFlow.Forms.XHtml for usage examples

running the flow monad

type FlowM view = StateT (MFlowState view)Source

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

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

setting parameters

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

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

Cookies

setCookieSource

Arguments

:: Monad m 
=> String

name

-> String

value

-> String

path

-> Maybe String

expires

-> FlowM view m () 

set an HTTP cookie