Safe Haskell | None |
---|
- Basic definitions
- Users
- User interaction
- formLets
- FormLet modifiers
- Caching widgets
- Widget combinators
- Normalized (convert to ByteString) widget combinators
- Formatting combinators
- Normalized (convert to ByteString) formatting combinators
- ByteString tags
- Normalization
- Running the flow monad
- controlling backtracking
- Setting parameters
- Cookies
- Ajax
- Requirements
- Utility
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 upto the programmer.
All the flow of requests and responses are coded by the programmer in a single procedure. Allthoug 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 syncronization 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 Wokflow 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 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 procedure in the FlowM monad. 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 <+> !*> , |*|. Widgets are also monoids, so they can
be combined as such.
- NEW IN THIS RELEASE
[
Runtime templates
]template
,edTemplate
,witerate
anddField
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. Enven less than usingautoRefresh
. - 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 sucession 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 behaviour 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 indetifier 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 (seeajaxSend
). 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, JavasScript online scipts, CSS files, online CSS and server processes
and any other instance of the
Requrement
class. Seerequires
andWebRequirements
content-management
- for templating and online edition of the content template. See
tFieldEd
tFieldGen
andtField
multilanguage
- see
mField
andmFieldEd
URLs to internal states
- if the web navigation is trough GET forms or links, an URL can express a direct path to the n-th 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 initate 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 behaviour 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 atributes to widgets. See the
<!
opèrator 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.
File Server
- With file caching. See MFlow.FileServer
- data FlowM v m a
- newtype View v m a = View {}
- data FormElm view a = FormElm [view] (Maybe a)
- class (Monoid view, Typeable view) => FormInput view where
- toByteString :: view -> ByteString
- toHttpData :: view -> HttpData
- fromStr :: String -> view
- fromStrNoEncode :: String -> view
- ftag :: String -> view -> view
- inred :: view -> view
- flink :: String -> view -> view
- flink1 :: String -> view
- finput :: Name -> Type -> Value -> Checked -> OnClick -> view
- ftextarea :: String -> Text -> view
- fselect :: String -> view -> view
- foption :: String -> view -> Bool -> view
- foption1 :: String -> Bool -> view
- formAction :: String -> view -> view
- attrs :: view -> Attribs -> view
- data Auth = Auth {}
- userRegister :: MonadIO m => UserStr -> PasswdStr -> m (Maybe String)
- setAuthMethod :: Auth -> IO ()
- userValidate :: (FormInput view, MonadIO m) => (UserStr, PasswdStr) -> m (Maybe view)
- isLogged :: MonadState (MFlowState v) m => m Bool
- setAdminUser :: MonadIO m => UserStr -> PasswdStr -> m ()
- getAdminName :: MonadIO m => m UserStr
- getCurrentUser :: MonadState (MFlowState view) m => m String
- getUserSimple :: (FormInput view, Typeable view) => FlowM view IO String
- getUser :: (FormInput view, Typeable view) => Maybe String -> View view IO (Maybe (UserStr, PasswdStr), Maybe String) -> FlowM view IO String
- userFormLine :: (FormInput view, Functor m, Monad m) => View view m (Maybe (UserStr, PasswdStr), Maybe PasswdStr)
- userLogin :: (FormInput view, Functor m, Monad m) => View view m (Maybe (UserStr, PasswdStr), Maybe String)
- logout :: (MonadIO m, MonadState (MFlowState view) m) => m ()
- userWidget :: (MonadIO m, Functor m, FormInput view) => Maybe String -> View view m (Maybe (UserStr, PasswdStr), Maybe String) -> View view m String
- login :: (MonadIO m, MonadState (MFlowState view) m) => String -> m ()
- userName :: User -> String
- ask :: FormInput view => View view IO a -> FlowM view IO a
- page :: FormInput view => View view IO a -> FlowM view IO a
- askt :: FormInput v => (Int -> a) -> View v IO a -> FlowM v IO a
- clearEnv :: MonadState (MFlowState view) m => m ()
- wstateless :: (Typeable view, FormInput view) => View view IO () -> Flow
- pageFlow :: (Monad m, Functor m, FormInput view) => String -> View view m a -> View view m a
- getString :: (FormInput view, Monad m) => Maybe String -> View view m String
- getInt :: (FormInput view, MonadIO m) => Maybe Int -> View view m Int
- getInteger :: (FormInput view, MonadIO m) => Maybe Integer -> View view m Integer
- getTextBox :: (FormInput view, Monad m, Typeable a, Show a, Read a) => Maybe a -> View view m a
- getMultilineText :: (FormInput view, Monad m) => Text -> View view m Text
- getBool :: (FormInput view, Monad m, Functor m) => Bool -> String -> String -> View view m Bool
- getSelect :: (FormInput view, Monad m, Typeable a, Read a) => View view m (MFOption a) -> View view m a
- setOption :: (Monad m, Show a, Eq a, Typeable a, FormInput view) => a -> view -> View view m (MFOption a)
- setSelectedOption :: (Monad m, Show a, Eq a, Typeable a, FormInput view) => a -> view -> View view m (MFOption a)
- getPassword :: (FormInput view, Monad m) => View view m String
- getRadio :: (Monad m, Functor m, FormInput view) => [String -> View view m (Radio a)] -> View view m a
- setRadio :: (FormInput view, MonadIO m, Read a, Typeable a, Eq a, Show a) => a -> String -> View view m (Radio a)
- setRadioActive :: (FormInput view, MonadIO m, Read a, Typeable a, Eq a, Show a) => a -> String -> View view m (Radio a)
- wlabel :: (Monad m, FormInput view) => view -> View view m a -> View view m a
- getCheckBoxes :: (FormInput view, Monad m) => View view m CheckBoxes -> View view m [String]
- genCheckBoxes :: (Monad m, FormInput view) => view -> View view m CheckBoxes
- setCheckBox :: (FormInput view, MonadIO m) => Bool -> String -> View view m CheckBoxes
- submitButton :: (FormInput view, Monad m) => String -> View view m String
- resetButton :: (FormInput view, Monad m) => String -> View view m ()
- whidden :: (Monad m, FormInput v, Read a, Show a, Typeable a) => a -> View v m a
- wlink :: (Typeable a, Show a, MonadIO m, FormInput view) => a -> view -> View view m a
- getRestParam :: (Read a, Typeable a, Monad m, Functor m, FormInput v) => FlowM v m (Maybe a)
- returning :: (Typeable a, Read a, Show a, Monad m, FormInput view) => ((a -> String) -> view) -> View view m a
- wform :: (Monad m, FormInput view) => View view m b -> View view m b
- firstOf :: (Monoid view, Monad m, Functor m) => [View view m a] -> View view m a
- manyOf :: (FormInput view, MonadIO m, Functor m) => [View view m a] -> View view m [a]
- wraw :: Monad m => view -> View view m ()
- wrender :: (Monad m, Functor m, Show a, FormInput view) => a -> View view m a
- notValid :: Monad m => view -> View view m a
- validate :: (FormInput view, Monad m) => View view m a -> (a -> WState view m (Maybe view)) -> View view m a
- noWidget :: (FormInput view, Monad m) => View view m a
- waction :: (FormInput view, Monad m) => View view m a -> (a -> FlowM view m b) -> View view m b
- wcallback :: Monad m => View view m a -> (a -> View view m b) -> View view m b
- clear :: Monad m => View v m ()
- wmodify :: (Monad m, FormInput v) => View v m a -> ([v] -> Maybe a -> WState v m ([v], Maybe b)) -> View v m b
- cachedWidget :: (MonadIO m, Typeable view, FormInput view, Typeable a, Executable m) => String -> Int -> View view Identity a -> View view m a
- wcached :: (MonadIO m, Typeable view, FormInput view, Typeable a, Executable m) => String -> Int -> View view Identity a -> View view m a
- wfreeze :: (MonadIO m, Typeable view, FormInput view, Typeable a, Executable m) => String -> Int -> View view m a -> View view m a
- (<+>) :: Monad m => View view m a -> View view m b -> View view m (Maybe a, Maybe b)
- (|*>) :: (MonadIO m, Functor m, Monoid view) => View view m r -> [View view m r'] -> View view m (Maybe r, Maybe r')
- (|+|) :: (Functor m, Monoid view, MonadIO m) => View view m r -> View view m r' -> View view m (Maybe r, Maybe r')
- (**>) :: (Functor m, Monad m) => View view m a -> View view m b -> View view m b
- (<**) :: (Functor m, Monad m) => View view m a -> View view m b -> View view m a
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
- (<*) :: Applicative f => forall a b. f a -> f b -> f a
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b
- (>:>) :: Monad m => View v m a -> View v m [a] -> View v m [a]
- (.<+>.) :: (Monad m, FormInput v, FormInput v1) => View v m a -> View v1 m b -> View ByteString m (Maybe a, Maybe b)
- (.|*>.) :: (Functor m, MonadIO m, FormInput v, FormInput v1) => View v m r -> [View v1 m r'] -> View ByteString m (Maybe r, Maybe r')
- (.|+|.) :: (Functor m, MonadIO m, FormInput v, FormInput v1) => View v m r -> View v1 m r' -> View ByteString m (Maybe r, Maybe r')
- (.**>.) :: (Monad m, Functor m, FormInput v, FormInput v1) => View v m a -> View v1 m b -> View ByteString m b
- (.<**.) :: (Monad m, Functor m, FormInput v, FormInput v1) => View v m a -> View v1 m b -> View ByteString m a
- (.<|>.) :: (Monad m, Functor m, FormInput v, FormInput v1) => View v m a -> View v1 m a -> View ByteString m a
- (<<<) :: (Monad m, Monoid view) => (view -> view) -> View view m a -> View view m a
- (++>) :: (Monad m, Monoid view) => view -> View view m a -> View view m a
- (<++) :: Monad m => View v m a -> v -> View v m a
- (<!) :: (Monad m, FormInput view) => View view m a -> Attribs -> View view m a
- (.<<.) :: FormInput view => (ByteString -> ByteString) -> view -> ByteString
- (.<++.) :: (Monad m, FormInput v, FormInput v') => View v m a -> v' -> View ByteString m a
- (.++>.) :: (Monad m, FormInput v, FormInput v') => v -> View v' m a -> View ByteString m a
- btag :: String -> Attribs -> ByteString -> ByteString
- bhtml :: Attribs -> ByteString -> ByteString
- bbody :: Attribs -> ByteString -> ByteString
- flatten :: Flatten (Maybe tree) list => tree -> list
- normalize :: (Monad m, FormInput v) => View v m a -> View ByteString m a
- runFlow :: (FormInput view, MonadIO m) => FlowM view m () -> Token -> m ()
- transientNav :: (Serialize a, Typeable view, FormInput view, Typeable a) => FlowM view IO a -> FlowM view (Workflow IO) a
- runFlowOnce :: (MonadIO m, FormInput view, Monad m) => FlowM view m () -> Token -> m ()
- runFlowIn :: (MonadIO m, FormInput view) => String -> FlowM view (Workflow IO) b -> FlowM view m b
- runFlowConf :: (FormInput view, MonadIO m) => FlowM view m a -> m a
- step :: (Serialize a, Typeable view, FormInput view, MonadIO m, Typeable a) => FlowM view m a -> FlowM view (Workflow m) a
- goingBack :: MonadState (MFlowState view) m => m Bool
- returnIfForward :: (Monad m, FormInput view) => b -> View view m b
- breturn :: Monad m => a -> FlowM v m a
- preventGoingBack :: (Functor m, MonadIO m, FormInput v) => FlowM v m () -> FlowM v m ()
- retry :: Monad m => View v m a -> View v m ()
- setHeader :: MonadState (MFlowState view) m => (view -> view) -> m ()
- addHeader :: Monad m => (view -> view) -> FlowM view m ()
- getHeader :: Monad m => FlowM view m (view -> view)
- setSessionData :: (Typeable a, MonadState (MFlowState view) m) => a -> m ()
- getSessionData :: (Typeable a, MonadState (MFlowState view) m) => m (Maybe a)
- delSessionData :: (Typeable a, MonadState (MFlowState view) m) => a -> m ()
- setTimeouts :: MonadState (MFlowState v) m => Int -> Integer -> m ()
- setCookie :: MonadState (MFlowState view) m => String -> String -> String -> Maybe Integer -> m ()
- ajax :: MonadIO m => (String -> View v m ByteString) -> View v m (String -> String)
- ajaxSend :: (Read a, MonadIO m) => View v m ByteString -> View v m a
- ajaxSend_ :: MonadIO m => View v m ByteString -> View v m ()
- class Requirements a where
- installRequirements :: (Monad m, FormInput view) => [a] -> m view
- data WebRequirement
- requires :: (Show a, Typeable a, MonadState (MFlowState view) m, Requirements a) => [a] -> m ()
- getLang :: MonadState (MFlowState view) m => m String
- genNewId :: MonadState (MFlowState view) m => m String
- getNextId :: MonadState (MFlowState view) m => m String
- changeMonad :: (Monad m, Executable m1) => View v m1 a -> View v m a
- data FailBack a
- fromFailBack :: FailBack t -> t
- toFailBack :: a -> FailBack a
- getRawParam :: (Read a, Typeable a, MonadState (MFlowState view) m, FormInput view) => String -> m (Maybe a)
Basic definitions
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.
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.
MonadTrans (View view) | |
Monad m => MonadState (MFlowState view) (View view m) | |
Monad m => Monad (View view m) | |
(Monad m, Functor m) => Functor (View view m) | |
(Functor m, Monad m) => Applicative (View view m) | |
(Functor m, Monad m) => Alternative (View view m) | |
MonadLoc (View v IO) | |
MonadIO m => MonadIO (View view m) | |
(Monad m, Functor m, Monoid a) => Monoid (View v m a) | |
Monad m => ADDATTRS (View Html m a) |
class (Monoid view, Typeable view) => FormInput view whereSource
toByteString :: view -> ByteStringSource
toHttpData :: view -> HttpDataSource
fromStr :: String -> viewSource
fromStrNoEncode :: String -> viewSource
ftag :: String -> 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
Users
setAuthMethod :: Auth -> IO ()Source
set an authentication method
userValidate :: (FormInput view, MonadIO m) => (UserStr, PasswdStr) -> m (Maybe view)Source
Authentication against userRegister
ed 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
getCurrentUser :: MonadState (MFlowState view) m => m StringSource
getUserSimple :: (FormInput view, Typeable view) => FlowM view IO StringSource
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 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 userRegister
ed
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 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") <+> 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 :: (MonadIO m, MonadState (MFlowState view) m) => m ()Source
logout. The user is reset to the anonymous
user
userWidget :: (MonadIO m, Functor m, FormInput view) => Maybe String -> View view m (Maybe (UserStr, PasswdStr), 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. 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.
login :: (MonadIO m, MonadState (MFlowState view) m) => String -> m ()Source
change the user
It is supposed that the user has been validated
User interaction
page :: FormInput view => View view IO a -> FlowM view IO aSource
A synonym of ask.
Maybe more appropiate 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 aSource
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
wstateless :: (Typeable view, FormInput view) => View view IO () -> FlowSource
Creates a stateless flow (see stateless
) whose behaviour is defined as a widget. It is a
higuer level form of the latter
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 ombinators and some additional ones
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 non empty String
getInt :: (FormInput view, 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, 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) => Text -> View view m TextSource
Display a multiline text box and return its content
getBool :: (FormInput view, Monad m, Functor 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, 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 <|>
getRadio :: (Monad m, Functor m, FormInput view) => [String -> View view m (Radio a)] -> View view m aSource
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
genCheckBoxes :: (Monad m, FormInput view) => view -> View view m CheckBoxesSource
Read the checkboxes dinamically 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 CheckBoxesSource
Display a text box and return the value entered if it is readable( Otherwise, fail the validation)
wlink :: (Typeable a, Show a, MonadIO m, FormInput view) => a -> view -> View view m aSource
Creates a link wiget. A link can be composed with other widget elements,
returning :: (Typeable a, Read a, Show a, Monad m, FormInput view) => ((a -> String) -> view) -> View view m aSource
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 bSource
Wrap a widget with form element within a form-action element.
Usually this is not necessary since this wrapping is done automatically by the Wiew
monad, unless
there are more than one form in the page.
firstOf :: (Monoid view, Monad m, Functor m) => [View view m a] -> View view m aSource
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.
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 aSource
Render a Show-able value and return it
FormLet modifiers
validate :: (FormInput view, Monad m) => View view m a -> (a -> WState view m (Maybe view)) -> 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
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. 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 significative 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 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.
wmodify :: (Monad m, FormInput v) => View v m a -> ([v] -> Maybe a -> WState v m ([v], Maybe b)) -> View v m bSource
change the rendering and the return value of a page. This is superseeded by page flows.
Caching widgets
:: (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
:: (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
:: (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 => 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 ask
ed 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, 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.
it has a infix priority infixr 5
(|+|) :: (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 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) => 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 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) => 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 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.
(<*>) :: 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, FormInput v, FormInput 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, FormInput v, FormInput 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, FormInput v, FormInput 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, FormInput v, FormInput v1) => View v m a -> View v1 m b -> View ByteString m bSource
(.**>.) x y = normalize x **> normalize y
(.<**.) :: (Monad m, Functor m, FormInput v, FormInput v1) => View v m a -> View v1 m b -> View ByteString m aSource
(.<**.) x y = normalize x <** normalize y
(.<|>.) :: (Monad m, Functor m, FormInput v, FormInput 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 within some formating.
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 aSource
Prepend formatting code to a widget
bold "enter name" ++ getString Nothing
It has a infix prority: infixr 6
higuer that <<<
and most other operators
(<!) :: (Monad m, FormInput view) => View view m a -> Attribs -> View view m aSource
Add attributes to the topmost tag of a widget
it has a fixity infix 8
Normalized (convert to ByteString) formatting combinators
Some combinators that convert the formatting of their arguments to lazy byteString
(.<<.) :: FormInput view => (ByteString -> ByteString) -> view -> ByteStringSource
(.<<.) w x = w $ toByteString x
(.<++.) :: (Monad m, FormInput v, FormInput v') => View v m a -> v' -> View ByteString m aSource
(.<++.) x v= normalize x <++ toByteString v
(.++>.) :: (Monad m, FormInput v, FormInput 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)
Running the flow monad
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
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 not log the response. it ever executes the computation
transient $ runFlow f === runFlow $ transientNav f
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 askingstoringretrieving user defined configurations by means of web formularies.
runFlowConf :: (FormInput view, MonadIO m) => FlowM view m a -> m aSource
transfer control to another flow. (experimental) transfer :: MonadIO m => String -> FlowM v m () transfer flowname = do t <- gets mfToken let t'= t{twfname= flowname} liftIO $ do (r,_) <- msgScheduler t' sendFlush t r
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) 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.
controlling backtracking
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 restar at the last page visited. No setting is necessary.
returnIfForward :: (Monad m, FormInput view) => b -> View view m bSource
return the result if going forward
If the process is backtraking, it does not validate, in order to continue the backtracking
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.
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"
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 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
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
addHeader :: Monad m => (view -> view) -> FlowM view m ()Source
Add another header embedded in the previous one
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.
delSessionData :: (Typeable a, MonadState (MFlowState view) m) => 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 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.
Cookies
:: 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
Ajax
:: MonadIO m | |
=> (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, MonadIO m) => View v m ByteString -> View v m aSource
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 => View v m ByteString -> View v m ()Source
Like ajaxSend
but the result is ignored
Requirements
class Requirements a whereSource
installRequirements :: (Monad m, FormInput view) => [a] -> m viewSource
data WebRequirement Source
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.
Varios widgets in the page can require the same element, MFlow will install it once.
Utility
getLang :: MonadState (MFlowState view) m => m StringSource
Return the user language. Now it is fixed to en
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
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.
fromFailBack :: FailBack t -> tSource
toFailBack :: a -> FailBack aSource
getRawParam :: (Read a, Typeable a, MonadState (MFlowState view) m, FormInput view) => String -> m (Maybe a)Source
return the value of a parameter from the environment