Announcement: Typeful [x]html combinators -- pre-release 0

Jon Fairbairn jon.fairbairn at cl.cam.ac.uk
Thu Jan 10 14:01:23 EST 2008


Tomasz Zielonka <tomasz.zielonka at gmail.com> writes:

> On Tue, Jan 08, 2008 at 02:43:08PM +0000, Jon Fairbairn wrote:
>> > It contains a monadic combinator library that checks
>> > proper nesting of HTML tags at compile time. The library
>> > also has an unchecked version,
>> 
>> It's possible that I only tried the unchecked version: I
>> just thought of an invalid example, read what documentation
>> I could find and generated some invalid html.
>
> That's an easy trap to fall into, especially because the author seems to
> use only unchecked combinators in examples ;-)

That's a bit of a strange thing to do.  Having gone to the
trouble of setting things up so that it can check (some
degree of) validity, why not use it? Isn't this what Haskell
is about?

Exploring WaSH isn't made easy by the documentation; if I try 

   build_document (html (head (title (text "foo"))
                   ## (body (h1 (text "foo")))))

-- essentially the first example from the pdf of the paper
"A Typed Representation for HTML and XML documents in
Haskell" -- I get 

<interactive>:1:16:
    No instance for (AddTo HTML HTML)
      arising from use of `html' at <interactive>:1:16-75
    Possible fix: add an instance declaration for (AddTo HTML HTML)
    In the first argument of `build_document', namely
        `(html ((head (title (text "foo"))) ## (body (h1 (text "foo")))))'
    In the expression:
        build_document
          (html ((head (title (text "foo"))) ## (body (h1 (text "foo")))))
    In the definition of `it':
        it = build_document
               (html ((head (title (text "foo"))) ## (body (h1 (text "foo")))))

and I don't know what's changed since the paper, or what I'm
doing wrong -- how do I get it to output something? (This is
with WASH.HTML.HTMLPrelude, but similar questions arise for
WASH.HTML.HTMLMonad98)

   unELT $ html (body (h1 $ img empty)) (make DOCUMENT)

outputs something, but it's not valid (no head), so that
can't be right.

>> Thiemann's thesis says

Actually, I meant the abovementioned paper.

>>    The current library implements neither inclusions nor
>>    exceptions.
>> 
>> So I hope I might be forgiven if I overlooked a difference
>> between the distribution and the thesis! Does the checked
>> version now enforce appendix B and prevent <a> appearing
>> anywhere within <a> and so on?
>
> I am not familiar with the HTML standards enough to understand
> everything you say here,

I'd sort-of hope that a proper HTML library would relieve
you of that responsibility!

> but I've just checked that you can't put <a>
> inside <a> using the checked combinators. But I can't say if it
> checks everything your library checks.

It doesn't: the issue is not <a> directly in <a>:

   *WASH.HTML.HTMLPrelude> :t a (a (text "foo"))

   <interactive>:1:3:
       No instance for (AddTo A A)
         arising from use of `a' at <interactive>:1:3-16
       Possible fix: add an instance declaration for (AddTo A A)
       In the first argument of `a', namely `(a (text "foo"))'

(it properly rejects that), but <a> anywhere within <a>:

   *WASH.HTML.HTMLPrelude> :t a (span (a (text "foo")))
   a (span (a (text "foo"))) :: (AddTo s A) => ELT s -> ELT s

which should also be rejected.

Here's what happens with my version:

   Prelude Typeful.Text.HTMLs> :t a << a << string "foo"

   <interactive>:1:5:
       No instance for (Is_A A_not_allowed_in_A)
         arising from use of `a' at <interactive>:1:5
       Possible fix:
         add an instance declaration for (Is_A A_not_allowed_in_A)
       In the first argument of `(<<)', namely `a'
       In the second argument of `(<<)', namely `a << (string "foo")'

and

   Typeful.Text.HTMLs> :t a << span << a << string "foo"

   <interactive>:1:13:
       No instance for (Is_A A_not_allowed_in_A)
         arising from use of `a' at <interactive>:1:13
       Possible fix:
         add an instance declaration for (Is_A A_not_allowed_in_A)
       In the first argument of `(<<)', namely `a'
       In the second argument of `(<<)', namely `a << (string "foo")'
       In the second argument of `(<<)', namely
           `span << (a << (string "foo"))'

I'm not especially enamoured of the "<<" syntax; it's just
what's used in the current html and xhtml libraries, so I
did something similar.


>> Another difference is that I haven't used any non-Haskell 98
>> constructs other than using Template Haskell to generate
>> class declarations and instances (were one so inclined, one
>> could get ghc to output the splices and [clean them up by
>> hand to] produce an entirely H98 version).
>
> I can't think of any non-haskell 98 extensions that were used in
> WASH/HTML, but I may be overlooking something. At least the interface of
> WASH.HTML.HTMLMonad98 looks quite standard.

count the number of arguments of the class WithHTML (or
AddTo in the above)... ;-)

-- 
Jón Fairbairn                                 Jon.Fairbairn at cl.cam.ac.uk



More information about the Libraries mailing list