Safe Haskell | None |
---|---|
Language | Haskell98 |
- (!>) :: c -> String -> c
- data FailBack a
- iCanFailBack :: [Char]
- repeatPlease :: [Char]
- noFailBack :: [Char]
- newtype Sup m a = Sup {}
- class MonadState s m => Supervise s m where
- fromFailBack :: FailBack t -> t
- toFailBack :: a -> FailBack a
- newtype FlowM v m a = FlowM {}
- breturn :: Monad m => a -> FlowM v m a
- liftSup :: Monad m => m a -> Sup m a
- type WState view m = StateT (MFlowState view) m
- type FlowMM view m = Sup (WState view m)
- data FormElm view a = FormElm view (Maybe a)
- newtype View v m a = View {}
- wcallback :: Monad m => View view m a -> (a -> View view m b) -> View view m b
- changeMonad :: (Monad m, Executable m') => View v m' a -> View v m a
- (<+>) :: (Monad m, FormInput view) => View view m a -> View view m b -> View view m (Maybe a, Maybe b)
- mix :: (Monad m, FormInput view) => View view m a -> View view m b -> View view m (Maybe a, Maybe b)
- (**>) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m b
- valid :: Monad m => View view m a1 -> View view m a
- (<**) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m a
- goingBack :: MonadState (MFlowState view) m => m Bool
- preventGoingBack :: (Functor m, MonadIO m, FormInput v) => FlowM v m () -> FlowM v m ()
- onBacktrack :: Monad m => m a -> FlowM v m a -> FlowM v m a
- compensate :: Monad m => m a -> m a -> FlowM v m a
- type Lang = String
- data NeedForm
- data MFlowState view = MFlowState {
- mfSequence :: Int
- mfCached :: Bool
- newAsk :: Bool
- inSync :: Bool
- mfSomeNotValidates :: Bool
- mfLang :: Lang
- mfEnv :: Params
- needForm :: NeedForm
- mfFileUpload :: Bool
- mfToken :: Token
- mfkillTime :: Int
- mfSessionTime :: Integer
- mfCookies :: [Cookie]
- mfHttpHeaders :: [(ByteString, ByteString)]
- mfHeader :: view -> view
- mfDebug :: Bool
- mfRequirements :: [Requirement]
- mfInstalledScripts :: [WebRequirement]
- mfData :: Map TypeRep Void
- mfAjax :: Maybe (Map String Void)
- mfSeqCache :: Int
- notSyncInAction :: Bool
- mfPath :: [String]
- mfPagePath :: [String]
- mfPrefix :: String
- mfPageFlow :: Bool
- linkMatched :: Bool
- mfAutorefresh :: Bool
- mfTrace :: [String]
- mfClear :: Bool
- type Void = Char
- mFlowState0 :: FormInput view => MFlowState view
- setSessionData :: (Typeable a, MonadState (MFlowState view) m) => a -> m ()
- delSessionData :: (MonadState (MFlowState view) m, Typeable * a) => a -> m ()
- getSessionData :: (Typeable a, MonadState (MFlowState view) m) => m (Maybe a)
- getSData :: (Monad m, Typeable a, Monoid v) => View v m a
- getSessionId :: MonadState (MFlowState v) m => m String
- getLang :: MonadState (MFlowState view) m => m String
- getToken :: MonadState (MFlowState view) m => m Token
- getEnv :: MonadState (MFlowState view) m => m Params
- stdHeader :: t -> t
- setHeader :: MonadState (MFlowState view) m => (view -> view) -> m ()
- getHeader :: Monad m => FlowM view m (view -> view)
- addHeader :: Monad m => (view -> view) -> FlowM view m ()
- setCookie :: MonadState (MFlowState view) m => String -> String -> String -> Maybe Integer -> m ()
- setParanoidCookie :: MonadState (MFlowState view) m => String -> String -> String -> Maybe Integer -> m ()
- setEncryptedCookie :: MonadState (MFlowState view) m => String -> String -> String -> Maybe Integer -> m ()
- setEncryptedCookie' :: (MonadState (MFlowState view) m, Show a, Functor f) => String -> String -> String -> f a -> ((ByteString, ByteString, ByteString, f ByteString) -> IO Cookie) -> m ()
- setHttpHeader :: MonadState (MFlowState view) m => ByteString -> ByteString -> m ()
- setTimeouts :: MonadState (MFlowState v) m => Int -> Integer -> m ()
- getWFName :: MonadState (MFlowState view) m => m String
- getCurrentUser :: MonadState (MFlowState view) m => m String
- type Name = String
- type Type = String
- type Value = String
- type Checked = Bool
- type OnClick = Maybe String
- normalize :: (Monad m, FormInput v) => View v m a -> View ByteString m 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 -> String -> view -> view
- attrs :: view -> Attribs -> view
- 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
- runFlow :: (FormInput view, MonadIO m) => FlowM view (Workflow m) () -> Token -> Workflow m ()
- inRecovery :: Int
- runFlowOnce :: (FormInput view, MonadIO m) => FlowM view (Workflow m) () -> Token -> Workflow m ()
- runFlowOnce1 :: (FormInput v, Monad m) => FlowM v (WF Stat m) a -> Token -> WF Stat m (FailBack Token, MFlowState v)
- startState :: FormInput view => Token -> MFlowState view
- runFlowOnce2 :: Monad m => MFlowState v -> FlowM v (WF Stat m) a -> WF Stat m (FailBack Token, MFlowState v)
- runFlowOnceReturn :: FormInput v => MFlowState v -> FlowM v m a -> Token -> m (FailBack a, MFlowState v)
- 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
- clearEnv :: MonadState (MFlowState view) m => m ()
- clearEnv' :: MonadState (MFlowState view) m => m ()
- step :: (Serialize a, Typeable view, FormInput view, MonadIO m, Typeable a) => FlowM view m a -> FlowM view (Workflow m) a
- transientNav :: (Serialize a, Typeable view, FormInput view, Typeable a) => FlowM view IO a -> FlowM view (Workflow IO) a
- data ParamResult v a
- = NoParam
- | NotValidated String v
- | Validated a
- valToMaybe :: ParamResult t a -> Maybe a
- isValidated :: ParamResult t t1 -> Bool
- fromValidated :: ParamResult t t1 -> t1
- getParam1 :: (Monad m, MonadState (MFlowState v) m, Typeable a, Read a, FormInput v) => String -> Params -> m (ParamResult v a)
- getRestParam :: (Read a, Typeable a, Monad m, Functor m, MonadState (MFlowState v) m, FormInput v) => m (Maybe a)
- getKeyValueParam :: (FormInput view, MonadState (MFlowState view) m, Typeable * a, Read a) => String -> m (Maybe a)
- readParam :: (Monad m, MonadState (MFlowState v) m, Typeable a, Read a, FormInput v) => String -> m (ParamResult v a)
- requires :: (Requirements a, MonadState (MFlowState view) m, Typeable * a, Show a) => [a] -> m ()
- unfold :: WebRequirement -> [WebRequirement]
- data Requirement = forall a . (Show a, Typeable a, Requirements a) => Requirement a
- class Requirements a where
- installRequirements :: (MonadState (MFlowState view) m, MonadIO m, FormInput view) => [a] -> m view
- installAllRequirements :: (MonadIO m, FormInput view) => WState view m view
- loadjsfile :: [Char] -> [Char]
- loadScript :: [Char]
- loadCallback :: a -> [Char] -> [Char]
- loadcssfile :: [Char] -> [Char]
- loadcss :: [Char] -> [Char]
- data WebRequirement
- installWebRequirements :: (MonadState (MFlowState view) m, MonadIO m, FormInput view) => [WebRequirement] -> m view
- strRequirement :: (MonadState (MFlowState view) m, MonadIO m) => WebRequirement -> m [Char]
- strRequirement' :: (MonadState (MFlowState view) m, MonadIO m) => WebRequirement -> m [Char]
- ajaxScript :: [Char]
- formPrefix :: (FormInput b, MonadState (MFlowState view1) m) => MFlowState view -> b -> Bool -> m b
- insertForm :: (FormInput view, Monad m) => View view m a -> View view m a
- controlForms :: (FormInput v, MonadState (MFlowState v) m) => MFlowState v -> MFlowState v -> v -> v -> m (v, Bool)
- currentPath :: MFlowState view -> [Char]
- genNewId :: MonadState (MFlowState view) m => m String
- getNextId :: MonadState (MFlowState view) m => m String
Documentation
iCanFailBack :: [Char] Source
repeatPlease :: [Char] Source
noFailBack :: [Char] Source
MonadTrans Sup | |
(Supervise s m, MonadState s m) => MonadState s (Sup m) | |
(Monad m, Applicative m) => Alternative (Sup m) | |
Supervise s m => Monad (Sup m) | |
(Monad m, Functor m) => Functor (Sup m) | |
(Monad m, Applicative m) => Applicative (Sup m) | |
(Supervise s m, MonadIO m) => MonadIO (Sup m) |
class MonadState s m => Supervise s m where Source
Nothing
Monad m => Supervise (MFlowState v) (WState v m) |
fromFailBack :: FailBack t -> t Source
toFailBack :: a -> FailBack a Source
the FlowM monad executes the page navigation. It perform Backtracking when necessary to synchronize when the user press the back button or when the user enter an arbitrary URL. The instruction pointer is moved to the right position within the procedure to handle the request.
However this is transparent to the programmer, who codify in the style of a console application.
breturn :: Monad m => a -> FlowM v m a Source
Use this instead of return to return from a computation with ask statements
This way when the user press the back button, the computation will execute back, to the returned code, according with the user navigation.
type WState view m = StateT (MFlowState view) m Source
View v m a
is a widget (formlet) with formatting v
running the monad m
(usually IO
) and which return a value of type a
It has Applicative
, Alternative
and Monad
instances.
Things to know about these instances:
If the View expression does not validate, ask will present the page again.
Alternative instance: Both alternatives are executed. The rest is as usual
Monad Instance:
The rendering of each statement is added to the previous. If you want to avoid this, use wcallback
The execution is stopped when the statement has a formlet-widget that does not validate and return an invalid response (So it will present the page again if no other widget in the expression validates).
The monadic code is executed from the beginning each time the page is presented or refreshed
use pageFlow
if your page has more than one monadic computation with dynamic behavior
use pageFlow
to identify each subflow branch of a conditional
For example:
pageFlow "myid" $ do r <- formlet1 liftIO $ ioaction1 r s <- formlet2 liftIO $ ioaction2 s case s of True -> pageFlow "idtrue" $ do .... False -> paeFlow "idfalse" $ do ... ...
Here if formlet2
do not validate, ioaction2
is not executed. But if formLet1
validates and the
page is refreshed two times (because formlet2
has failed, see above),then ioaction1
is executed two times.
use cachedByKey
if you want to avoid repeated IO executions.
Monoid view => MonadTrans (View view) | |
(FormInput view, Monad m) => MonadState (MFlowState view) (View view m) | |
(FormInput view, Functor m, Monad m) => Alternative (View view m) | |
(FormInput view, Monad m) => Monad (View view m) | |
(Monad m, Functor m) => Functor (View view m) | |
(Monoid view, Functor m, Monad m) => Applicative (View view m) | |
FormInput v => MonadLoc (View v IO) | |
(FormInput view, MonadIO m) => MonadIO (View view m) | |
(FormInput v, Monad m, Functor m, Monoid a) => Monoid (View v m a) |
wcallback :: Monad m => View view m a -> (a -> View view m b) -> View view m b Source
It is a callback in the view monad. The callback rendering substitutes the widget rendering when the latter is validated, without affecting the rendering of other widgets. This allow the simultaneous execution of different behaviors in different widgets in the same page. The inspiration is the callback primitive in the Seaside Web Framework that allows similar functionality (See http://www.seaside.st)
This is the visible difference with waction
callbacks, which execute a
a flow in the FlowM monad that takes complete control of the navigation, while wactions are
executed within the same page.
changeMonad :: (Monad m, Executable m') => View v m' a -> View v m a Source
Execute the widget in a monad and return the result in another.
(<+>) :: (Monad m, FormInput view) => View view m a -> View view m b -> View view m (Maybe a, Maybe b) infixr 2 Source
Join two widgets in the same page
the resulting widget, when 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) -> ..
mix :: (Monad m, FormInput view) => 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) -> ..
(**>) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m b infixr 1 Source
The first elem result (even if it is not validated) is discarded, and the second is returned
. This contrast with the applicative operator *>
which fails the whole validation if
the validation of the first elem fails.
The first element is displayed however, as happens in the case of *>
.
Here w's
are widgets and r's
are returned values
(w1 <* w2)
will return Just r1
only if w1 and w2 are validated
(w1 <** w2)
will return Just r1
even if w2 is not validated
it has a low infix priority: infixr 1
(<**) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m a infixr 1 Source
The second elem result (even if it is not validated) is discarded, and the first is returned
. This contrast with the applicative operator *>
which fails the whole validation if
the validation of the second elem fails.
The second element is displayed however, as in the case of <*
.
see the <**
examples
it has a low infix priority: infixr 1
goingBack :: MonadState (MFlowState view) m => m Bool Source
True if the flow is going back (as a result of the back button pressed in the web browser). Usually this check is nos necessary unless conditional code make it necessary
menu= do
mop <- getGoStraighTo
case mop of
Just goop -> goop
Nothing -> do
r <- ask
option1 <|> option2
case r of
op1 -> setGoStraighTo (Just goop1) >> goop1
op2 -> setGoStraighTo (Just goop2) >> goop2
This pseudocode below would execute the ask of the menu once. But the user will never have the possibility to see the menu again. To let him choose other option, the code has to be change to
menu= do mop <- getGoStraighTo back <-goingBack
case (mop,back) of (Just goop,False) -> goop _ -> do r <-ask
option1 <|> option2 case r of op1 -> setGoStraighTo (Just goop1) >> goop1 op2 -> setGoStraighTo (Just goop2) >> goop2
However this is very specialized. Normally the back button detection is not necessary. In a persistent flow (with step) even this default entry option would be completely automatic, since the process would restart at the last page visited.
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 a Source
executes the first computation when going forward and the second computation when backtracking. Depending on how the second computation finishes, the flow will resume forward or backward.
compensate :: Monad m => m a -> m a -> FlowM v m a Source
less powerful version of onBacktrack
: The second computation simply undo the effect of
the first one, and the flow continues backward ever. It can be used as a rollback mechanism in
the context of long running transactions.
data MFlowState view Source
MFlowState | |
|
(FormInput view, Monad m) => MonadState (MFlowState view) (View view m) | |
Monad m => MonadState (MFlowState v) (FlowM v m) | |
Monad m => Supervise (MFlowState v) (WState v m) | |
(FormInput v, Serialize a) => Serialize (a, MFlowState v) | |
Typeable (* -> *) MFlowState |
mFlowState0 :: FormInput view => MFlowState view Source
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 :: (MonadState (MFlowState view) m, Typeable * a) => 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.
getSData :: (Monad m, Typeable a, Monoid v) => View v m a Source
getSessionData specialized for the View monad. if Nothing, the monadic computation does not continue.
getSessionId :: MonadState (MFlowState v) m => m String Source
Return the session identifier
getLang :: MonadState (MFlowState view) m => m String Source
Return the user language. Now it is fixed to "en"
getToken :: MonadState (MFlowState view) m => m Token Source
getEnv :: MonadState (MFlowState view) m => m Params Source
setHeader :: MonadState (MFlowState view) m => (view -> view) -> m () Source
Set the header-footer that will enclose the widgets. It must be provided in the same formatting than them, although with normalization to ByteStrings any formatting can be used
This header uses XML trough Haskell Server Pages (http://hackage.haskell.org/package/hsp)
setHeader $ c -> <html> <head> <title> my title </title> <meta name= "Keywords" content= "sci-fi" />) </head> <body style= "margin-left:5%;margin-right:5%"> <% c %> </body> </html>
This header uses Text.XHtml
setHeader $ c ->thehtml
<< (header
<< (thetitle
<< title +++meta
! [name
"Keywords",content "sci-fi"])) +++body
! [style
"margin-left:5%;margin-right:5%"] c
This header uses both. It uses byteString tags
setHeader $ c ->bhtml
[] $btag
"head" [] $ (toByteString
(thetitle << title)append
toByteString
name= "Keywords" content= "sci-fi" /)append
bbody
[("style", "margin-left:5%;margin-right:5%")] c
addHeader :: Monad m => (view -> view) -> FlowM view m () Source
Add another header embedded in the previous one
:: 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
:: MonadState (MFlowState view) m | |
=> String | name |
-> String | value |
-> String | path |
-> Maybe Integer | Max-Age in seconds. Nothing for a session cookie |
-> m () |
:: MonadState (MFlowState view) m | |
=> String | name |
-> String | value |
-> String | path |
-> Maybe Integer | Max-Age in seconds. Nothing for a session cookie |
-> m () |
setEncryptedCookie' :: (MonadState (MFlowState view) m, Show a, Functor f) => String -> String -> String -> f a -> ((ByteString, ByteString, ByteString, f ByteString) -> IO Cookie) -> m () Source
:: 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 beginning.
2) In persistent flows it set the session state timeout for the flow, that is persistent. If the flow is not persistent, it has no effect.
As the other state primitives, it can be run in the Flow and in the View monad
transient
flows restart anew.
persistent flows (that use step
) restart at the last saved execution point, unless
the session time has expired for the user.
getWFName :: MonadState (MFlowState view) m => m String Source
getCurrentUser :: MonadState (MFlowState view) m => m String Source
class (Monoid view, Typeable view) => FormInput view where Source
Minimal interface for defining the basic form and link elements. The core of MFlow is agnostic
about the rendering package used. Every formatting (either HTML or not) used with MFlow must have an
instance of this class.
See "MFlow.Forms.Blaze.Html for the instance for blaze-html" MFlow.Forms.XHtml for the instance
for Text.XHtml
and MFlow.Forms.HSP for the instance for Haskell Server Pages.
toByteString, toHttpData, fromStr, fromStrNoEncode, ftag, inred, flink, finput, ftextarea, fselect, foption, formAction, attrs
toByteString :: view -> ByteString Source
toHttpData :: view -> HttpData Source
fromStr :: String -> view Source
fromStrNoEncode :: String -> view Source
ftag :: String -> view -> view Source
flink :: String -> view -> view Source
flink1 :: String -> view Source
finput :: Name -> Type -> Value -> Checked -> OnClick -> view Source
ftextarea :: String -> Text -> view Source
fselect :: String -> view -> view Source
foption :: String -> view -> Bool -> view Source
foption1 :: String -> Bool -> view Source
formAction :: String -> String -> view -> view Source
:: (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
runFlow :: (FormInput view, MonadIO m) => FlowM view (Workflow m) () -> Token -> Workflow m () Source
Execute the Flow, in the FlowM view m
monad. It is used as parameter of hackMessageFlow
waiMessageFlow
or addMessageFlows
The flow is executed in a loop. When the flow is finished, it is started again
main= do addMessageFlows [("noscript",transient $ runFlow mainf)] forkIO . run 80 $ waiMessageFlow adminLoop
inRecovery :: Int Source
runFlowOnce :: (FormInput view, MonadIO m) => FlowM view (Workflow m) () -> Token -> Workflow m () Source
runFlowOnce1 :: (FormInput v, Monad m) => FlowM v (WF Stat m) a -> Token -> WF Stat m (FailBack Token, MFlowState v) Source
startState :: FormInput view => Token -> MFlowState view Source
runFlowOnce2 :: Monad m => MFlowState v -> FlowM v (WF Stat m) a -> WF Stat m (FailBack Token, MFlowState v) Source
runFlowOnceReturn :: FormInput v => MFlowState v -> FlowM v m a -> Token -> m (FailBack a, MFlowState v) Source
runFlowIn :: (MonadIO m, FormInput view) => String -> FlowM view (Workflow IO) b -> FlowM view m b Source
Run a persistent flow inside the current flow. It is identified by the procedure and the string identifier. Unlike the normal flows, that run within infinite loops, runFlowIn executes once. In subsequent executions, the flow will get the intermediate responses from the log and will return the result without asking again. This is useful for asking once, storing in the log and subsequently retrieving user defined configurations by means of persistent flows with web formularies.
runFlowConf :: (FormInput view, MonadIO m) => FlowM view m a -> m a Source
To unlift a FlowM computation. useful for executing the configuration generated by runFLowIn outside of the web flow (FlowM) monad
clearEnv :: MonadState (MFlowState view) m => m () Source
Clears the environment
clearEnv' :: MonadState (MFlowState view) m => m () Source
clear the request paramters and the rest path.
step :: (Serialize a, Typeable view, FormInput view, MonadIO m, Typeable a) => FlowM view m a -> FlowM view (Workflow m) a Source
Stores the result of the flow in a persistent log. When restarted, it get the result
from the log and it does not execute it again. When no results are in the log, the computation
is executed. It is equivalent to step
but in the FlowM monad.
transientNav :: (Serialize a, Typeable view, FormInput view, Typeable a) => FlowM view IO a -> FlowM view (Workflow IO) a Source
To execute transient flows as if they were persistent, it can be used instead of step, but it does log nothing. Thus, it is faster and convenient when no session state must be stored beyond the lifespan of the server process.
transient $ runFlow f === runFlow $ transientNav f
data ParamResult v a Source
(Read v, Read a) => Read (ParamResult v a) | |
(Show v, Show a) => Show (ParamResult v a) |
valToMaybe :: ParamResult t a -> Maybe a Source
isValidated :: ParamResult t t1 -> Bool Source
fromValidated :: ParamResult t t1 -> t1 Source
getParam1 :: (Monad m, MonadState (MFlowState v) m, Typeable a, Read a, FormInput v) => String -> Params -> m (ParamResult v a) Source
getRestParam :: (Read a, Typeable a, Monad m, Functor m, MonadState (MFlowState v) m, FormInput v) => m (Maybe a) Source
getKeyValueParam :: (FormInput view, MonadState (MFlowState view) m, Typeable * a, Read a) => String -> m (Maybe a) Source
return the value of a post or get param in the form ?param=value¶m2=value2...
readParam :: (Monad m, MonadState (MFlowState v) m, Typeable a, Read a, FormInput v) => String -> m (ParamResult v a) Source
requires :: (Requirements a, MonadState (MFlowState view) m, Typeable * a, Show a) => [a] -> m () Source
Requirements are JavaScripts, Stylesheets or server processes (or any instance of the Requirement
class) that are included in the
Web page or in the server when a widget specifies this. requires
is the
procedure to be called with the list of requirements.
Various widgets in the page can require the same element, MFlow will install it once.
unfold :: WebRequirement -> [WebRequirement] Source
data Requirement Source
forall a . (Show a, Typeable a, Requirements a) => Requirement a |
class Requirements a where Source
installRequirements :: (MonadState (MFlowState view) m, MonadIO m, FormInput view) => [a] -> m view Source
installAllRequirements :: (MonadIO m, FormInput view) => WState view m view Source
loadjsfile :: [Char] -> [Char] Source
loadScript :: [Char] Source
loadCallback :: a -> [Char] -> [Char] Source
loadcssfile :: [Char] -> [Char] Source
data WebRequirement Source
installWebRequirements :: (MonadState (MFlowState view) m, MonadIO m, FormInput view) => [WebRequirement] -> m view Source
strRequirement :: (MonadState (MFlowState view) m, MonadIO m) => WebRequirement -> m [Char] Source
strRequirement' :: (MonadState (MFlowState view) m, MonadIO m) => WebRequirement -> m [Char] Source
ajaxScript :: [Char] Source
formPrefix :: (FormInput b, MonadState (MFlowState view1) m) => MFlowState view -> b -> Bool -> m b Source
insertForm :: (FormInput view, Monad m) => View view m a -> View view m a Source
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 :: MFlowState view -> [Char] Source
genNewId :: MonadState (MFlowState view) m => m String Source
Generate a new string. Useful for creating tag identifiers and other attributes.
If the page is refreshed, the identifiers generated are the same.
getNextId :: MonadState (MFlowState view) m => m String Source
Get the next identifier that will be created by genNewId