MFlow-0.4.2: stateful, RESTful web framework

Safe HaskellNone

MFlow.Forms.Internals

Description

 

Synopsis

Documentation

data FailBack a Source

Constructors

BackPoint a 
NoBack a 
GoBack 

newtype Sup m a Source

Constructors

Sup 

Fields

runSup :: m (FailBack a)
 

Instances

MonadTrans Sup 
(Supervise s m, MonadState s m) => MonadState s (Sup m) 
Supervise s m => Monad (Sup m) 
(Monad m, Functor m) => Functor (Sup m) 
(Supervise s m, MonadIO m) => MonadIO (Sup m) 

class MonadState s m => Supervise s m whereSource

Methods

supBack :: s -> m ()Source

supervise :: m (FailBack a) -> m (FailBack a)Source

Instances

Monad m => Supervise (MFlowState v) (WState v m) 

newtype FlowM v m a Source

the FlowM monad executes the page navigation. It perform Backtracking when necessary to syncronize 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.

Constructors

FlowM 

Fields

runFlowM :: FlowMM v m a
 

Instances

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

flowM :: FlowMM v m a -> FlowM v m aSource

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

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.

liftSup :: Monad m => m a -> Sup m aSource

type WState view m = StateT (MFlowState view) mSource

type FlowMM view m = Sup (WState view m)Source

data FormElm view a Source

Constructors

FormElm [view] (Maybe a) 

Instances

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 behaviour

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

MonadTrans (View view) 
(FormInput view, Monad m) => MonadState (MFlowState view) (View view m) 
(FormInput view, Monad m) => Monad (View view m) 
(Monad m, Functor m) => Functor (View view m) 
(Functor m, Monad m) => Applicative (View view m) 
(FormInput view, Functor m, Monad m) => Alternative (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) 
Monad m => ADDATTRS (View Html m a) 

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

It is a callback in the view monad. The callback rendering substitutes the widget rendering when the latter is validated, without afecting the rendering of other widgets. This allow the simultaneous execution of different behaviours 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 whithin the same page.

clear :: (FormInput v, Monad m) => View v m ()Source

changeMonad :: (Monad m, Executable m1) => View v m1 a -> View v m aSource

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

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 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.

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"

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

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.

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

less powerflul 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.

data NeedForm Source

Constructors

HasForm 
HasElems 
NoElems 

Instances

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

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

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

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

getSessionId :: MonadState (MFlowState v) m => m StringSource

Return the session identifier

getLang :: MonadState (MFlowState view) m => m StringSource

Return the user language. Now it is fixed to en

stdHeader :: t -> tSource

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, altrough 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

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

Return the current header

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

Add another header embedded in the previous one

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

setHttpHeaderSource

Arguments

:: MonadState (MFlowState view) m 
=> ByteString

name

-> ByteString

value

-> m () 

Set an HTTP Response header

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 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.

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 las saved execution point, unless the session time has expired for the user.

class (Monoid view, Typeable view) => FormInput view whereSource

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 -> ByteStringSource

toHttpData :: view -> HttpDataSource

fromStr :: String -> viewSource

fromStrNoEncode :: String -> viewSource

ftag :: String -> view -> viewSource

inred :: view -> viewSource

flink :: String -> view -> viewSource

flink1 :: String -> viewSource

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

ftextarea :: String -> Text -> viewSource

fselect :: String -> view -> viewSource

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

foption1 :: String -> Bool -> viewSource

formAction :: String -> view -> viewSource

attrs :: view -> Attribs -> viewSource

cachedWidgetSource

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

wcachedSource

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

wfreezeSource

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

runFlow :: (FormInput view, MonadIO m) => FlowM view m () -> Token -> 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

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

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

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 te 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 aSource

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

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

Clears the environment

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

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.

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

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

data ParamResult v a Source

Constructors

NoParam 
NotValidated String v 
Validated a 

Instances

(Read v, Read a) => Read (ParamResult v a) 
(Show v, Show a) => Show (ParamResult v a) 

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

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

requires :: (Show a, Typeable a, MonadState (MFlowState view) m, Requirements 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.

data Requirement Source

Constructors

forall a . (Show a, Typeable a, Requirements a) => Requirement a 

class Requirements a whereSource

Methods

installRequirements :: (Monad m, FormInput view) => [a] -> m viewSource

loadjsfile :: [Char] -> [[Char]] -> [Char]Source

loadjs :: t -> tSource

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

formPrefix :: (MonadState (MFlowState view1) m, FormInput b) => MFlowState view -> [b] -> Bool -> m bSource

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

insert a form tag if the widget has form input fields. If not, it does nothing

controlForms :: (FormInput v, MonadState (MFlowState v) m) => MFlowState v -> MFlowState v -> [v] -> [v] -> m ([v], Bool)Source

currentPath :: Bool -> Int -> [[Char]] -> [Char] -> [Char]Source

genNewId :: MonadState (MFlowState view) m => m StringSource

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 StringSource

get the next ideitifier that will be created by genNewId