[Haskell-cafe] It's not a monad - what is it? looking for nice syntactic sugar, customizable do notation?

Marc Weber marco-oweber at gmx.de
Tue Sep 2 00:12:56 EDT 2008


Context: Basic xml validation of vxml does work now.
      So I'm looking for a convinient way to use it.

(1) My first approach:

  putStrLn $ xml $
    ((html_T << ( head_T << (title_T <<< "hw")
                         << (link_T `rel_A` "stylesheet" `type_A` "text/css" `href_A` "style.css")
              ))
             <<  ( body_T << ((script_T `type_A` "text/javascript") <<< "document.writeln('hi');" )
                       << (div_T `onclick_A` "alert('clicked');" `style_A` "color:#F79"
                              <<< "text within the div"
                        )
              ) )

  comment:
  That's straight forward:
   >> : add subelement
  >>> : add text
  However having to use many parenthesis to get nesting is awkward.


(2) My second idea:

  (#) = flip (.)

  putStrLn $ xml $
    ( headC ( (titleC (<<< "hw"))
            # (linkC (rel_AF "stylesheet" # type_AF "text/css" # href_AF "style.css" ) )
            )
    # bodyC ( scriptC ( type_AF "text/javascript" # text "document.writeln('hi');" )
            # divC ( onclick_AF "alert('clicked')" # style_AF "color:#F79"
                  # text "text within the div" )
            )
    ) html_T

  comment:
  headC a b = head with context where a is a function adding subelements then
              adding itself to the elemnt passed by b
  Thus headC id parent would add headC to parent
  I don't feel much luckier this way
  
  
(3) Third idea:
  

  xmlWithInnerIO <- execXmlT $ do
    xmlns "http://www.w3.org/1999/xhtml" >> lang "en-US" >> xml:lang "en-US"
    head $ title $ text "minimal"
    body $ do
      args <- lift $ getArgs
      h1 $ text "minimal"
      div $ text $ "args passed to this program: " ++ (show args)

  comment:
  WASH is using do notation which is really convinient.
  elements beeing at the same level can be concatenated by new lines,
  subelemnts can be added really nice as well.
  However: This can't work.
  (>>) :: m a -> m b -> m b
  but I need this
  (>>) :: m a -> m' b -> m'' b
  or
  (>>) :: m st a -> m st' b -> m st'' b
  along with functional dependencies that st' can be deduced from st and st''
  from st'..
  There are some happy cases eg when having a DTD such as (a | b)* because the
  state will "loop" and not change.. But this is no solution.

(4) Another way would be defining
<< : (add subelement
<|> : concatenate same level (+++) of xhtml lib

html << head << title <<< "title"
             <|> meta ..
     <|> body << div
              <|> div

However you already see the trouble.. ghc will read this as

(html << (head << (title <<< "title")))
             <|> meta ..
             <|> (body << div)  -- body should be added to html, not to head!
             <|> div

There would be a solution using different fixities
html <<1 head <<2 title <<< "title"
              <|2> meta 
     <|1> body <<2 div
              <|2> div <<3 div <<4 div

so that <<4 binds stronger than <<3 etc..
But I think thats awkward as well.

(5) But ghc is rich, I can think of another way: Quasi Quoting..
[$makeAFun|
  html do
    head do
      meta $1
      link $2
  body do
    div $3
    div $4
|] (Dollar1 "bar") (Dollar2 "foo") (Dollar3 "foo3") (Dollar4 "foo4")

the wrapper type sDollar{1,2,3,4} aren't necessary, but they will help eg if
you remove the $2 line. They also enable you using a substitute more than once.
    

(6) Another solution would be writing a preprocesor reusing alreday exsting
code (HSP or WASH ?) or the haskell-src packages?

Is there yet another solution which I've missed?




I still think that (3) would be superiour..
Is there a way to define my own >>= and >> functions such as:

  {-# define custom do doX; 
    (>>=) : mybind , >> : "my>>" #-}
  body $ doX
    args <- lift $ getArgs
This would be terrific.

Sincerly
Marc Weber


More information about the Haskell-Cafe mailing list