MFlow-0.2.0.8: continuation-based Web framework without continuations.

Safe HaskellNone

MFlow.Forms.Widgets

Contents

Description

Some dynamic widgets, widgets that dynamically edit content in other widgets, widgets for templating, content management and multilanguage. And some primitives to create other active widgets.

Synopsis

User Management

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

Present a user form if not logged in. Otherwise, the user name and a logout link is presented. The paremeters and the behaviour are the same as userWidget. Only the display is different

maybeLogout :: (MonadIO m, Functor m, FormInput v) => View v m ()Source

Display a logout link if the user is logged. Nothing otherwise

Active widgets

wEditListSource

Arguments

:: (Typeable a, Read a, FormInput view, Functor m, MonadIO m, Executable m) 
=> (view -> view)

The holder tag

-> (Maybe String -> View view Identity a)

the contained widget, initialized by a string

-> [String]

The initial list of values.

-> String

The id of the button or link that will create a new list element when clicked

-> View view m [a] 

Inside a tag, it add and delete widgets of the same type. When the form is submitted or a wlink is pressed, this widget return the list of validated widgets. the event for adding a new widget is attached , as a click event to the element of the page with the identifier wEditListAdd that the user will choose.

This example add or delete editable text boxes, with two initial boxes with hi, how are you as values. Tt uses blaze-html:

wautocompleteSource

Arguments

:: (Show a, MonadIO m, FormInput v) 
=> Maybe String

Initial value

-> (String -> IO a)

Autocompletion procedure: will receive a prefix and return a list of strings

-> View v m String 

Present an autocompletion list, from a procedure defined by the programmer, to a text box.

wautocompleteList :: (Functor m, MonadIO m, Executable m, FormInput v) => String -> (String -> IO [String]) -> [String] -> View v m [String]Source

A specialization of selectAutocompleteEdit which make appear each option choosen with a checkbox that deletes the element when uncheched. The result, when submitted, is the list of selected elements.

wautocompleteEditSource

Arguments

:: (Typeable a, MonadIO m, Functor m, Executable m, FormInput v) 
=> String

the initial text of the box

-> (String -> IO [String])

the autocompletion procedure: receives a prefix, return a list of options.

-> (Maybe String -> View v Identity a)

the widget to add, initialized with the string entered in the box

-> [String]

initial set of values

-> View v m [a]

resulting widget

Produces a text box. It gives a autocompletion list to the textbox. When return is pressed in the textbox, the box content is used to create a widget of a kind defined by the user, which will be situated above of the textbox. When submitted, the result of this widget is the content of the created widgets (the validated ones).

wautocompleteList is an specialization of this widget, where the widget parameter is fixed, with a checkbox that delete the eleement when unselected . This fixed widget is as such (using generic FormElem class tags):

 ftag "div"    <<< ftag "input" mempty
                               `attrs` [("type","checkbox")
                                       ,("checked","")
                                       ,("onclick","this.parentNode.parentNode.removeChild(this.parentNode)")]
               ++> ftag "span" (fromStr $ fromJust x )
               ++> whidden( fromJust x)

Editing widgets

delEditedSource

Arguments

:: (Typeable v, Typeable a, MonadIO m, MonadState (MFlowState view) m) 
=> ByteString

identifier

-> [View v m1 a] 
-> m ()

withess

Deletes the list of edited widgets for a certain identifier and with the type of the witness widget parameter

getEdited :: (Typeable v, Typeable a, MonadState (MFlowState view) m) => ByteString -> m [View v m1 a]Source

Return the list of edited widgets (added by the active widgets) for a given identifier

prependWidgetSource

Arguments

:: (Typeable a, MonadIO m, Executable m, FormInput v) 
=> ByteString

jquery selector

-> View v Identity a

widget to prepend

-> View v m ByteString

string returned with the jquery string to be executed in the browser

Return the javascript to be executed on the browser to prepend a widget to the location identified by the selector (the bytestring parameter), The selector must have the form of a jquery expression . It stores the added widgets in the edited list, that is accessed with getEdited

The resulting string can be executed in the browser. ajax will return the code to execute the complete ajax roundtrip. This code returned by ajax must be in an eventhabdler.

This example code will insert a widget in the div when the element with identifier clickelem is clicked. when the form is sbmitted, the widget values are returned and the list of edited widgets are deleted.

    id1<- genNewId
    let sel= "$('#" <>  B.pack id1 <> "')"
    callAjax <- ajax . const $ prependWidget sel wn
    let installevents= "$(document).ready(function(){\
              \$('#clickelem').click(function(){"++callAjax "''"++"});})"

    requires [JScriptFile jqueryScript [installevents] ]
    ws <- getEdited sel
    r <-  (div  <<< manyOf ws) <! [("id",id1)]
    delEdited sel ws'
    return  r

appendWidget :: (Typeable a, MonadIO m, Executable m, FormInput v) => ByteString -> View v Identity a -> View v m ByteStringSource

Like prependWidget but append the widget instead of prepend.

setWidget :: (Typeable a, MonadIO m, Executable m, FormInput v) => ByteString -> View v Identity a -> View v m ByteStringSource

L ike prependWidget but set the entire content of the selector instead of prepending an element

Content Management

tField :: (MonadIO m, Functor m, Executable m, FormInput v) => Key -> View v m ()Source

Read the field value and present it without edition.

tFieldEd :: (Functor m, MonadIO m, Executable m, FormInput v) => Key -> v -> View v m ()Source

A widget that display the content of an html, But if logged as administrator, it permits to edit it in place. So the editor could see the final appearance of what he write in the page.

When the administrator double click in the paragraph, the content is saved and identified by the key. Then, from now on, all the users will see the saved content instead of the code content.

The content is saved in a file by default (texts in this versions), but there is a configurable version (tFieldGen). The content of the element and the formatting is cached in memory, so the display is, theoretically, very fast.

THis is an example of how to use the content management primitives (in demos.blaze.hs):

 textEdit= do
   setHeader $ \t -> html << body << t

   let first=  p << i <<
                  (El.span << text "this is a page with"
                  <> b << text " two " <> El.span << text "paragraphs")

       second= p << i << text "This is the original text of the second paragraph"

       pageEditable =  (tFieldEd "first"  first)
                   **> (tFieldEd "second" second)

   ask $   first
       ++> second
       ++> wlink () (p << text "click here to edit it")

   ask $ p << text "Please login with admin/admin to edit it"
           ++> userWidget (Just "admin") userLogin

   ask $   p << text "now you can click the field and edit them"
       ++> p << b << text "to save the edited field, double click on it"
       ++> pageEditable
       **> wlink () (p << text "click here to see it as a normal user")

   logout

   ask $   p << text "the user sees the edited content. He can not edit"
       ++> pageEditable
       **> wlink () (p << text "click to continue")

   ask $   p << text "When text are fixed,the edit facility and the original texts can be removed. The content is indexed by the field key"
       ++> tField "first"
       **> tField "second"
       **> p << text "End of edit field demo" ++> wlink () (p << text "click here to go to menu")

tFieldGenSource

Arguments

:: (MonadIO m, Functor m, Executable m, FormInput v) 
=> Key 
-> (Key -> IO v)

the read procedure, user defined

-> (Key -> v -> IO ())

the write procedure, user defiend

-> View v m () 

Like tFieldEd with user-configurable storage.

Multilanguage

mFieldEd :: (Functor m, Executable m, MonadIO m, FormInput v) => [Char] -> v -> View v m ()Source

A multilanguage version of tFieldEd. For a field with key it add a suffix with the two characters of the language used.

mField :: (Functor m, Executable m, MonadIO m, FormInput v) => [Char] -> View v m ()Source

A multilanguage version of tField