| Safe Haskell | None | 
|---|
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.
- autoRefresh :: (MonadIO m, FormInput v) => View v m a -> View v m a
- noAutoRefresh :: [(String, String)]
- appendUpdate :: (MonadIO m, FormInput v) => View v m a -> View v m a
- prependUpdate :: (MonadIO m, FormInput v) => View v m a -> View v m a
- push :: FormInput v => UpdateMethod -> Int -> View v IO () -> View v IO ()
- data UpdateMethod
- lazy :: (FormInput v, Functor m, MonadIO m) => v -> View v m a -> View v m a
- datePicker :: (Monad m, FormInput v) => String -> Maybe String -> View v m (Int, Int, Int)
- getSpinner :: (MonadIO m, Read a, Show a, Typeable a, FormInput view) => String -> Maybe a -> View view m a
- wautocomplete :: (Show a, MonadIO m, FormInput v) => Maybe String -> (String -> IO a) -> View v m String
- wdialog :: (Monad m, FormInput v) => String -> String -> View v m a -> View v m a
- userFormOrName :: (Functor m, MonadIO m, FormInput [t], FormInput t) => Maybe String -> View [t] m (Maybe (UserStr, PasswdStr), Maybe String) -> View [t] m String
- maybeLogout :: (MonadIO m, Functor m, FormInput v) => View v m ()
- wlogin :: (MonadIO m, Functor m, FormInput v) => View v m ()
- wEditList :: (Typeable a, Read a, FormInput view, Functor m, MonadIO m, Executable m) => (view -> view) -> (Maybe String -> View view Identity a) -> [String] -> String -> View view m [a]
- wautocompleteList :: (Functor m, MonadIO m, Executable m, FormInput v) => String -> (String -> IO [String]) -> [String] -> View v m [String]
- wautocompleteEdit :: (Typeable a, MonadIO m, Functor m, Executable m, FormInput v) => String -> (String -> IO [String]) -> (Maybe String -> View v Identity a) -> [String] -> View v m [a]
- delEdited :: (Typeable v, Typeable a, MonadIO m, MonadState (MFlowState view) m) => ByteString -> [View v m1 a] -> m ()
- getEdited :: (Typeable v, Typeable a, MonadState (MFlowState view) m) => ByteString -> m [View v m1 a]
- setEdited :: (Typeable view1, Typeable a, MonadState (MFlowState view) m) => ByteString -> [(String, View view1 m1 a)] -> m ()
- prependWidget :: (Typeable a, MonadIO m, Executable m, FormInput v) => ByteString -> View v Identity a -> View v m ByteString
- appendWidget :: (Typeable a, MonadIO m, Executable m, FormInput v) => ByteString -> View v Identity a -> View v m ByteString
- setWidget :: (Typeable a, MonadIO m, Executable m, FormInput v) => ByteString -> View v Identity a -> View v m ByteString
- tField :: (MonadIO m, Functor m, Executable m, FormInput v) => Key -> View v m ()
- tFieldEd :: (Functor m, MonadIO m, Executable m, FormInput v) => UserStr -> Key -> v -> View v m ()
- htmlEdit :: (Monad m, FormInput v) => [String] -> UserStr -> View v m a -> View v m a
- edTemplate :: (MonadIO m, FormInput v, Typeable a) => UserStr -> Key -> View v m a -> View v m a
- dField :: (Monad m, FormInput view) => View view m b -> View view m b
- template :: (MonadIO m, FormInput v, Typeable a) => Key -> View v m a -> View v m a
- witerate :: (MonadIO m, Functor m, FormInput v) => View v m a -> View v m a
- tfieldKey :: TField -> Key
- mFieldEd :: (Functor m, Executable m, MonadIO m, FormInput v) => UserStr -> [Char] -> v -> View v m ()
- mField :: (Functor m, Executable m, MonadIO m, FormInput v) => [Char] -> View v m ()
- insertForm :: (Monad m, FormInput view) => View view m a -> View view m a
- readtField :: FormInput a => a -> [Char] -> IO a
- writetField :: FormInput view => String -> view -> IO ()
Ajax refreshing of widgets
autoRefresh :: (MonadIO m, FormInput v) => View v m a -> View v m aSource
Capture the form or link submissions and send them via jQuery AJAX. The response is the new presentation of the widget, that is updated. No new page is generated but the functionality is equivalent. Only the activated widget rendering is updated in the client, so a widget with autoRefresh can be used in heavyweight pages. If AJAX/JavaScript are not available, the widget is refreshed normally, via a new page.
autoRefresh encloses the widget in a form tag if it includes form elements.
If there are more than one autoRefresh, they must be enclosed within pageFlow elements
noAutoRefresh :: [(String, String)]Source
In some cases, it is neccessary that a link or form inside a autoRefresh or update block
 should not be autorefreshed, since it produces side effects in the rest of the page that
 affect to the rendering of the whole. If you like to refresh the whole page, simply add
 noAutoRefresh attribute to the widget to force the refresh of the whole page when it is activated.
That behaviour is common at the last sentence of the autoRefresh block.
This is a cascade menu example.
 r <- page $ autoRefresh $ ul <<< do
        li <<< wlink OptionA << "option A"
        ul <<< li <<< (wlink OptionA1 << "Option A1" <! noAutoRefresh)
           <|> li <<< (wlink OptionA2 << "Option A2" <! noAutoRefresh)
        <|>...
           maybe other content
 case r of
    OptionA1 -> pageA1
    OptionA2 -> pageA2
when option A is clicked, the two sub-options appear with autorefresh. Only the two
 lines are returned by the server using AJAX. but when Option A1-2 is pressed we want to
 present other pages, so we add the noAutorefresh attribute.
NOTE: the noAutoRefresh attribute should be added to the a/ or form/ tags.
appendUpdate :: (MonadIO m, FormInput v) => View v m a -> View v m aSource
does the same than autoRefresh but append the result of each request to the bottom of the widget
all the comments and remarks of autoRefresh apply here
prependUpdate :: (MonadIO m, FormInput v) => View v m a -> View v m aSource
does the same than autoRefresh but prepend the result of each request before the current widget content
all the comments and remarks of autoRefresh apply here
push :: FormInput v => UpdateMethod -> Int -> View v IO () -> View v IO ()Source
continously execute a widget and update the content.
 The update method specify how the update is done. Html means a substitution of content.
 The second parameter is the delay for the next retry in case of disconnection, in milliseconds.
It can be used to show data updates in the server. The widget is executed in a different process than
  the one of the rest of the page.
 Updates in the session context are not seen by the push widget. It has his own context.
 To communicate with te widget, use DBRef's or TVar and the
 STM semantics for waiting updates using retry.
Widgets in a push can have links and forms, but since they are asunchonous, they can not return inputs. but they can modify the server state. push ever return an invalid response to the calling widget, so it never triggers the advance of the navigation.
This example is a counter increased each second:
 pushIncrease= do
   tv <- liftIO $ newTVarIO 0
   page $ push 0 Html $ do
       n <- atomic $ readTVar tv
       atomic $ writeTVar tv $ n + 1
       liftIO $ threadDelay 1000000
       b << (show n) ++> noWidget
This other simulates a console output that echoes what is entered in a text box below. It has two widgets: a push output in append mode and a text box input. The communication uses a TVar. The push widget wait for updates in the TVar. because the second widget uses autoRefresh, all happens in the same page.
It is recommended to add a timeout to the push widget, like in the example:
  pushSample=  do
   tv <- liftIO $ newTVarIO $ Just "init"
   page $ push Append 1000 (disp tv) <** input tv
   where
   disp tv= do
       setTimeouts 100 0
       line <- tget tv
       p <<  line ++> noWidget
   input tv= autoRefresh $ do
       line <- getString Nothing <** submitButton "Enter"
       tput tv line
   tput tv x = atomic $ writeTVar  tv ( Just x)  !> "WRITE"
   tget tv= atomic $ do
       mr <- readTVar tv
       case mr of
          Nothing -> retry
          Just r -> do
           writeTVar tv Nothing
           return r
lazy :: (FormInput v, Functor m, MonadIO m) => v -> View v m a -> View v m aSource
takes as argument a widget and delay the load until it is visible. The renderring to be shown during the load is the specified in the first parameter. The resulting lazy widget behaves programatically in the same way.
It can lazily load recursively. It means that if the loaded widget has a lazy statement, it will be honored as well.
Because a widget can contain arbitrary HTML, images or javascript, lazy can be used to lazy load anything.
To load a image:
lazy temprendering $ wraw ( img ! href imageurl)
or
lazy temprendering $ img ! href imageurl ++> noWidget
JQueryUi widgets
datePicker :: (Monad m, FormInput v) => String -> Maybe String -> View v m (Int, Int, Int)Source
present the JQuery datepicker calendar to choose a date. The second parameter is the configuration. Use "()" by default. See http:jqueryui.comdatepicker
getSpinner :: (MonadIO m, Read a, Show a, Typeable a, FormInput view) => String -> Maybe a -> View view m aSource
show the jQuery spinner widget. the first parameter is the configuration . Use "()" by default. See http:jqueryui.com/spinner
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 the JQuery autocompletion list, from a procedure defined by the programmer, to a text box.
wdialog :: (Monad m, FormInput v) => String -> String -> View v m a -> View v m aSource
present a jQuery dialog with a widget. When a button is pressed it return the result. The first parameter is the configuration. To make it modal, use "({modal: true})" see http://jqueryui.com/dialog/ for the available configurations.
The enclosed widget will be wrapped within a form tag if the user do not encloses it using wform.f
User Management
userFormOrName :: (Functor m, MonadIO m, FormInput [t], FormInput t) => Maybe String -> View [t] m (Maybe (UserStr, PasswdStr), Maybe String) -> View [t] 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
wlogin :: (MonadIO m, Functor m, FormInput v) => View v m ()Source
If not logged, it present a page flow which askm for the user name, then the password if not logged
If logged, it present the user name and a link to logout
normally to be used with autoRefresh and pageFlow when used with other widgets.
Active widgets
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:
  r <-  ask  $   addLink
              ++> br
              ++> (El.div `wEditList`  getString1 $  ["hi", "how are you"]) "addid"
              <++ br
              <** submitButton "send"
  ask $   p << (show r ++ " returned")
      ++> wlink () (p << text " back to menu")
  mainmenu
  where
  addLink = a ! At.id  "addid"
              ! href "#"
              $ text "add"
  delBox  =  input ! type_   "checkbox"
                   ! checked ""
                   ! onclick "this.parentNode.parentNode.removeChild(this.parentNode)"
  getString1 mx= El.div  <<< delBox ++> getString  mx <++ br
wautocompleteList :: (Functor m, MonadIO m, Executable m, FormInput v) => String -> (String -> IO [String]) -> [String] -> View v m [String]Source
A specialization of wutocompleteEdit which make appear each chosen option with
 a checkbox that deletes the element when uncheched. The result, when submitted, is the list of selected elements.
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 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
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
setEdited :: (Typeable view1, Typeable a, MonadState (MFlowState view) m) => ByteString -> [(String, View view1 m1 a)] -> m ()Source
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 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= "$('#" <>  fromString 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
a text field. Read the cached field value and present it without edition.
tFieldEd :: (Functor m, MonadIO m, Executable m, FormInput v) => UserStr -> Key -> v -> View v m ()Source
A widget that display the content of an html, But if the user has edition privileges, it permits to edit it in place. So the editor could see the final appearance of what he writes.
When the user click the save, 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.
htmlEdit :: (Monad m, FormInput v) => [String] -> UserStr -> View v m a -> View v m aSource
Creates a rich text editor aroun a text field or a text area widget. This code:
 page $ p "Insert the text"
    ++> htmlEdit ["bold","italic"] ""
           (getMultilineText "" <! [("rows","3"),("cols","80")]) <++ br
    <** submitButton "enter"
Creates a rich text area with bold and italic buttons. The buttons are the ones alled in the nicEdit editor.
edTemplate :: (MonadIO m, FormInput v, Typeable a) => UserStr -> Key -> View v m a -> View v m aSource
permits the edition of the rendering of a widget at run time. Once saved, the new rendering becomes the new rendering of the widget for all the users. You must keep the active elements of the template
the first parameter is the user that has permissions for edition. the second is a key that identifies the template.
dField :: (Monad m, FormInput view) => View view m b -> View view m bSource
Present a widget via AJAX if it is within a witerate context. In the first iteration it present the
 widget surrounded by a placeholder. subsequent iterations will send just the javascript code
 necessary for the refreshing of the placeholder.
template :: (MonadIO m, FormInput v, Typeable a) => Key -> View v m a -> View v m aSource
Does the same than template but without the edition facility
witerate :: (MonadIO m, Functor m, FormInput v) => View v m a -> View v m aSource
Permits to iterate the presentation of data andor input fields and widgets within a web page that does not change. The placeholders are created with dField. Both are widget modifiers: The latter gets a widget and create a placeholder in the page that is updated via ajax. The content of the update is the rendering of the widget at each iteration. The former gets a wider widget which contains dField elements and permit the iteration. Whenever a link or a form within the witerate widget is activated, the result is the placeholders filled with the new html content. This content can be data, a input field, a link or a widget. No navigation happens.
This permits even faster updates than autoRefresh. since the latter refresh the whole widget and it does not permits modifications of the layout at runtime.
When edTemplate or template is used on top of witerate, the result is editable at runtime, and the span placeholders generated, that are updated via ajax can be relocated within the layout of the template.
Additionally, contrary to some javascript frameworks, the pages generated with this mechanism are searchable by web crawlers.
Multilanguage
mFieldEd :: (Functor m, Executable m, MonadIO m, FormInput v) => UserStr -> [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
utility
insertForm :: (Monad m, FormInput view) => View view m a -> View view m aSource
insert a form tag if the widget has form input fields. If not, it does nothing
readtField :: FormInput a => a -> [Char] -> IO aSource
writetField :: FormInput view => String -> view -> IO ()Source