Wednesday, November 14, 2012

MFlow now supports blaze-html

MFlow now supports blaze.html.

This example  uses Blaze.Html . It is almost identical to the Text.XHtml version.

It show almost all of the functionalities of MFlow, so it has a lot of imports. Here the header and the main function is displayed:

{-# LANGUAGE OverloadedStrings, ScopedTypeVariables, DeriveDataTypeable, NoMonomorphismRestriction #-}
module Main where
import MFlow.Hack  -- hiding (ask)
import Hack.Handler.SimpleServer
import MFlow.Forms.Blaze.Html
import MFlow.Forms.Widgets
import MFlow.Forms.Ajax
import Text.Blaze.Html5 as El
import Text.Blaze.Html5.Attributes as At hiding (step)
import Text.Blaze.Internal(text)
import Data.String
--import MFlow.Forms.Test
import MFlow
import MFlow.FileServer
import MFlow.Forms.Ajax
import MFlow.Forms.Admin
import MFlow.Forms
import Data.TCache
import Control.Monad.Trans
import Data.Typeable

import Control.Concurrent
import Control.Exception as E
import qualified Data.ByteString.Char8 as SB
import qualified Data.Vector as V
import Data.Maybe
import Data.Monoid

--test= runTest [(15,"shop")]

main= do
   syncWrite SyncManual
   setFilesPath ""
   addFileServerWF
   addMessageFlows [(""  ,transient $ runFlow mainf),
                    ("shop"    ,runFlow shopCart)]
   run 80 hackMessageFlow

   adminLoop

stdheader c= html << body << (p << text "You can press the back button" <> c)

data Options= CountI | CountS | TextEdit |Shop | Action | Ajax | Select deriving (Bounded, Enum,Read, Show,Typeable)

mainf=   do
       setHeader stdheader
       r <- ask="ask" br="br" nbsp="nbsp"> wlink TextEdit (b << text "Content Management")
               <|>  br ++> wlink Shop (b << text "example of transfer to another flow (shopping)")
               <|>  br ++> wlink CountI (b << text "increase an Int")
               <|>  br ++> wlink CountS (b << text "increase a String")
               <|>  br ++> wlink Action (b << text "Example of a string widget with an action")
               <|>  br ++> wlink Ajax (b << text "Simple AJAX example")
               <|>  br ++> wlink Select (b << text "select options")
               <++ (br <> linkShop) -- this is an ordinary XHtml link


       case r of
             CountI    ->  clickn 0
             CountS    ->  clicks "1"
             Action    ->  actions 1
             Ajax      ->  ajaxsample
             Select    ->  options
             TextEdit  ->  textEdit
             Shop      ->  transfer "shop"
       mainf

       where
       linkShop= a ! href  "shop" << text "shopping"




This example uses the last version of MFlow at https://github.com/agocorona/MFlow.
It uses the last version of  Workflow  https://github.com/agocorona/Workflow

MFlow: now the widgets can express requirements

A widget can need the installation of a client script, a CSS or download them. Also it can need a server process installed. But other widgets in the same page could need the same script. To avoid duplications, and to make easy the development of separated widgets maintaining the modularity, I added requirements.

type Script= String
type OnLoadScript= String
type File= String
data WebRequirement= CSSFile String
                   | CSS Script
                   | JScriptFile File [OnLoadScript]
                   | JScript Script
                   | ServerProc (String, Token -> Workflow IO ())

[OnLoadScript] are scripts called when the script file is loaded.

The syntax is as such:


ask $  requires[WebRequirement
    >> rest of the page

here >> is the monadic operator



For example this widget show set of options in from data from the serves via AJAX,  is defined in MFlow.Forms.Widgets, insert two javascript files, a CSS file and  a script. It can be combined with other widgets that require also these scripts, but the page creation process will just insert a single script tag or css link. The programmer no longer has to care about the requirements of each widget


selectAutocomplete serverproc = do 
    requires [JScript ajaxScript 
             ,JScriptFile jqueryScript [events]
             ,CSSFile jqueryCSS
             ,JScriptFile jqueryUi []]
             
    ajaxc <- ajaxcommand="ajaxcommand" attr="attr" font="font" text1="text1" value="value">
                         $ \u -> do
                                 r <- font="font" serverproc="serverproc" u="u">
                                 return $ jaddtoautocomp r

    getCheckBoxes
      (thediv ! [strAttr "id" "users"] <<< noWidget )
      <++ input ![thetype "text"
                 ,value "select users"
                 ,strAttr "id" "text1"
                 ,strAttr "oninput" ajaxc
                 ,strAttr "autocomplete" "off"]



This example uses the last version of MFlow at https://github.com/agocorona/MFlow.
It uses the last version of  Workflow  https://github.com/agocorona/Workflow

Monday, November 12, 2012

Content management in MFlow


I Just added some templating/content management to MFlow that IMHO is more flexible and simple than proper templating or content management approaches.

tFieldEd key html

is a widget that display the content of  html as is, But if logged as administrator, it permits to edit this chunk of html in place. So the editor could see the real appearance of what he write in the page while editing. When the administrator double click in the paragraph, the content is saved and identified by the key. Then, from now on the users will see the content of the saved paragraph, not the original one in the code.

The content is saved in a file by default ("texts" in this versions), but there is a configurable version (tFieldGen). The html content and his formating is cached in memory, so the display is very fast.

In case that the content has been fiixed and it don´t need further editions, 

 tField key

just read and present the edited content. tFieldEd is not longer needed.


There are also multilingual content management primitives mField and mFieldEd 


This demo shows in four steps how a typical process of content edition would work.

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


    let first=  p << italics << 

                   (thespan << "this is a page with"
                   +++ bold << " two " +++ thespan << "paragraphs") 
                   
        second= p << italics << "This is the original text. This is the second paragraph"
         
        pageEditable =  (tFieldEd "first"  first)
                    **> (tFieldEd "second" second)
        
    ask $   first
        ++> second
        ++> wlink () (p << "click here to edit it")
    
    setAdminUser "admin" "admin"
    
    ask $ p << "Please login with admin/admin to edit it"
            ++> userWidget (Just "admin") userLogin
    
    ask $   p << "now you can click the field and edit them"
        ++> p << bold << "to save the edited field, double click on it"
        ++> pageEditable
        **> wlink () (p << "click here to see it as a normal user")
        
    logout
    
    ask $   p << "the user sees the edited content. He can not edit it"
        ++> pageEditable   
        **> wlink () (p << "click to continue")
      
    ask $   p << "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 << "End of edit field demo" ++> wlink () (p << "click here to go to menu")


        


This example uses the last version of MFlow at https://github.com/agocorona/MFlow.
It uses the last version of  Workflow  https://github.com/agocorona/Workflow