[Haskell-cafe] Need help with VXML again (fun deps and forall types)

Marc Weber marco-oweber at gmx.de
Sun Nov 2 08:47:50 EST 2008


Some time I've announced that I'm working on VXML, a validating xml
library.

The use case which makes trouble is elem+ (one or more)

<!ELEMENT root (a|b|(c,d+))*>

This example is encoded in this way:


root -> St 1

 id :1
   endable : True
   a -> St 1
   b -> St 1
   c -> St 12


 id :11
   endable : True
   (a|b|c) -> St 1
   d -> St 11

 id :12
   endable : False
   d -> St 11

to be read as:
When creating a new root element start with state 1, then expect one of
a,b,c subelemnts.

If subelement c is added continue with state 12. The element may not be finalized
(endable false because a "d" is expected). Following that we end in a
loop at state 11 which is endable when only adding more d subelemnts.

in VXML it looks like this
  print $ fStr $ runRoot $ vdo
          -- forceElements
          c e
          d e -- first,  result has state 12    A
          d e -- second, result has state 11    X
          d e -- thrd,   result has state 11 
          d e -- fourth, result has state 11    Y
              -- ... 

Now I'd like to do something convinient such as
  foldr1 (>>) print $ [1..10]

I've called the corresponding function in VXML vxmlgtgt because it can
be used like a monad and even do notation is supported using the vdo cpp
macro rebinding (>>), (>>=) and return.
Obviously I can only use foldr from X up to Y because A has a different
return type.

If you download the latest version of the library 
  (git clone git://mawercer.de/vxml; git checkout fc160ab  # is master branch )

you see that it actually works quite fine

  -- helper function: 
  vxmlSeqPlus_ (f,fl) = f `vxmlgtgt`  (foldr1 vxmlgtgt fl)

  -- usage example from testSimple.hs, note that both (d e) have different types
  vxmlSeqPlus_ ((d e), replicate 9 (d e))

d is actually a function creating the d element requiring a
function as first argument which adds attrubutes and subelemnts (e is a
nop here)

This all makes d having a type which looks rather complicated:
el*: the result type (String only in the current implementation)

  data VXML st el_
            st2 el2_
            st3 el3_ a
            = VXML {
            runVVXML ::     
                            (PT st el_ -> PT st2 el2_)  -- [1]
                      -> (a, PT st el_ -> PT st3 el3_)  -- [2]
            }
[1] : st -> st2 : The function which is passed
[2] : st -> st3 : The type of function which is returned
                  taking a function modyfiying the parent and adding "d" resulting in st3
                  (st3 is either State12 in A, or State11 in Y talking about the example given above)

Its even getting more interesting now:
Because I'd like to use different result types (String, ByteString, ...)
I've used a type var to represent that type. I've called them el el2 el3
etc. When finally creating the document by using runRoot the result
types propagates through the xml tree by functional dependencies.

An example is the AddElT class which actually does add a subelement:

  class AddElT est el_ 
               estc elc_
               est2 el2_
      | est estc -> est2          -- result state is determined by parent and  child element state
      , est est2 estc el2_ -> el_  -- the result type of child and parent privious sibling are determined by the el2_ return type and the element states
      , est est2 estc el2_ -> elc_
      where
    addElT :: PT est el_ -> PT estc elc_ -> PT est2 el2_

The instance has constraints like this determining el_ elc_ and st2
  instance (
      , DetermineElAddEl 
              (NYV (Element elType AttrsOk st hchs)) el2
              cest2 elc2
              (NYV (Element elType AttrsOk st2 HTrue)) el3

      , Consume st (Elem celType) st2
      [..]
    ) =>  AddElT [..]

Determining states form leafs to the root then propagating String or
ByteString result type form the root to the leaf depending on states
works fine until I start trying to use shortcut for the foldr1 example
above.

Instead of 
  vxmlSeqPlus_ ((d e), replicate 9 (d e))

I'd like to write this. Of course the lamba here is polymorphic because
it must return State 12 the first time and State 11 in the following
cases.
  vxmlMapSeqPlus_ (\_ -> d e) [1..10] -- Ex I 

It's implementation is straight forward:
vxmlMapSeqPlus_ f (x:xs) = vxmlSeqPlus_ (f x, map f xs)
vxmlMapSeqPlus_ _ [] = error "vxmlSeqPlus has been called with empty list"

My attempt to assign a type looks like this:
  vxmlMapSeqPlus_ :: ( VXMLMonad m  st el  st2 el2  st3 el3  st3 el3
                     , VXMLMonad m  st el  st3 el3  st3 el3  st3 el3
                     ) => (forall st' elA st'' elB . t -> m  st el  st' elA  st'' elB ())
                    -> [t]
                    -> m st el st2 el2 st3 el3 ()
  vxmlMapSeqPlus_ f (x:xs) = vxmlSeqPlus_ (f x , map f xs)
  vxmlMapSeqPlus_ _ [] = error "vxmlSeqPlus has been called with empty list"


  where

  class VXMLMonad m  st el_  st2 el2_  st3 el3_  st4 el4_ where
    vxmlgtgt ::  m st el_  st2 el2_  st3 el3_  a
              -> m st el_  st3 el3_  st4 el4_  b
              -> m st el_  st2 el2_  st4 el4_  b
    vxmlgtgt a b = vxmlbind a $ const b
    vxmlbind :: m st el_  st2 el2_  st3 el3_ a
                -> (a -> m st el_  st3 el3_  st4 el4_  b)
                -> m st el_  st2 el2_  st4 el4_  b

However when compiling the example (Ex I) there are a bunch of errors
telling me that ghc can't find the matching instances caused by missing
specialization of st.. That is ghc does no longer determine the
resulting state based on parent and previous childs. Without state it
can't propagate the el type ...

You can see both examples in testSimple.hs
   vxmlSeqPlus_ ((d e), replicate 9 (d e))
   vxmlMapSeqPlus_ (\n -> d e ) [1..10]

So my question is: The second line does work fine, the first one
dosen't. How to write vxmlMapSeqPlus_ so that I can compile the example?

          vxmlMapSeqPlus_ (\n -> d e ) [1..10]
          (d e) `vxmlgtgt` (foldr1 vxmlgtgt $ map (const $ d e) [2..10])


If you want to try this with ghc older than 6.10 you'll have to rewrite
the vdo notation using vxmlbind and vxmlgtgt..


Do you have any idea how to make this work as expected?
That's the last issue preventing me from trying to use it in real life
projects.

Sincerly
Marc Weber


More information about the Haskell-Cafe mailing list